2 In the revised syntax of parsers the "?" is now a "??" like in the orignal
3 syntax to not conflict with optional labels.
5 - [29 Jun 05] Add private row types. Make "private" a type constructor
6 "TyPrv" rather than a flag. (Jacques)
8 - [09 Jun 04] Moved "-no_quot" option from pa_o to camlp4, enabling to
9 use it indepently fom pa_o.cmo.
11 - [17 Nov 04] Renamed "loc" into "_loc", introducing an incompatibility
12 with existing code (3.08.x and before). Such code can generally run
13 unmodified using the -loc option (camlp4 -loc "loc").
16 ------------------------
17 - [07 Oct 04] Changes in the interfaces plexer.mli and pcaml.mli:
18 - plexer.mli: introduced a new lexer building function `make_lexer',
19 similar to `gmake', but returning a triple of references in addition
20 (holding respectively the character number of the beginning of the
21 current line, the current line number and the name of the file being
23 - pcaml.mli: a new value `position'. A global reference to a triple like
24 the one mentioned above.
25 - [07 Sep 04] Camlp4 grammars `error recovery mode' now issues a warning
26 when used (but this warning is disabled by default).
28 Camlp4 Version 3.08.[01]
29 ------------------------
30 - [05 Jul 04] creation of the `unmaintained' directory:
31 pa_format, pa_lefteval, pa_ocamllex, pa_olabl, pa_scheme and pa_sml
32 go there, each in its own subdir. Currently, they compile fine.
33 - [05 Jul 04] pa_ifdef, subsumed by pa_macro since 3.07, prints a warning
34 when loaded, encouraging use of pa_macro.
35 - [01 July 04] profiled versions of Camlp4 libs are *NOT* installed
36 by default (not even built). To build and install them, uncomment
37 the line PROFILING=prof in camlp4/config/Makefile.tpl, and then
38 make opt.opt && make install
39 - [22-23 June 04] `make install' now installs also pa_[or].cmx, pa_[or]p.cmx,
40 pa_[or]_fast.cmx, and odyl.cmx
41 - [12 may 04] Added to the camlp4 tools the -version option that prints
42 the version number, in the same way as the other ocaml tools.
43 - [12 may 04] Locations are now handled as in OCaml. The main benefit
44 is that line numbers are now correct in error messages. However, this
45 slightly changes the interface of a few Camlp4 modules (see ICHANGES).
46 ** Warning: Some contribs of the camlp4 distribution are broken because
47 of this change. In particular the scheme/lisp syntaxes.
48 - [20 nov 03] Illegal escape sequences in strings now issue a warning.
53 - [29 Sep 03] Camlp4 code now licensed under the LGPL minus clause 6.
54 - [09 Sep 03] Added tokens LABEL and OPTLABEL in plexer, and use them in
55 both parsers (ocaml and revised). There was, afaik, no other way to fix
56 ambiguities (bugs) in parsing labels and type constraints.
58 Camlp4 Version 3.07 beta1
59 ________________________
61 - [July 03] Updated the ocaml/camlp4 CVS tree with the camlp4
62 "parallel" CVS tree, which becomes obsolete from now on.
63 Added support for recursive modules, private data constructors, and
64 new syntaxes for integers (int32, nativeint, ...).
67 -----------------------
69 - [02 Dec 02] In AST predefined quotation, changed antiquotations for
70 "rec", "mutable": now all are with coercion "opt": $opt:...$ (instead
71 of "rec" and "mut"). Added antiquotation for "private". Cleaned up
72 the entries for "methods" and for labelled and optional parameters.
73 - [29 Nov 02] Removed all "extract_crc" stuff no more necessary with
74 the new interface of Dynlink.
75 - [26 Nov 02] Added ability to use "#use" directives in compiled files.
76 - [21 Nov 02] Changed Scheme syntax for directives: now, e.g. #load "file"
77 is written: # (load "file"). Added directives in "implem", "interf" and
79 - [20 Nov 02] Added Grammar.glexer returning the lexer used by a
80 grammar. Also added a field in Token.glexer type to ask lexers to
81 record the locations of the comments.
82 - [04 Nov 02] Added option -no_quot with normal syntax (pa_o.cmo):
83 don't parse quotations (it allows to use e.g. <:> as a valid token).
84 - [31 Oct 02] Added pa_macro.cmo (to replace pa_ifdef.cmo which is
85 kept for compatibility, but deprecated). The extended statements
86 allow de definitions of macros and conditional compilation like
88 - [29 Oct 02] Changed pretty printers of the three main syntaxes: if
89 the locations of input are not correct, do no more raise End_of_file
90 when displaying the inter-phrases (return: the input found up to eof
91 if not empty, otherwise the value of the -sep parameter if not empty,
92 otherwise the string "\n").
93 - [25 Oct 02] Added option -records in pa_sml.cmo: generates normal
94 OCaml records instead of objects (the user must be sure that there
95 are no names conflicts).
96 - [22 Oct 02] Added Plexer.specific_space_dot: when set to "true", the
97 next call to Plexer.gmake returns a lexer where the dot preceded by
98 spaces (space, tab, newline, etc.) return a different token than when
99 not preceded by spaces.
100 - [19 Oct 02] Added printer in Scheme syntax: pr_scheme.cmo and the
101 extension pr_schemep.cmo which rebuilts parsers.
102 - [15 Oct 02] Now, in case of syntax error, the real input file name is
103 displayed (can be different from the input file, because of the possibility
104 of line directives, typically generated by /lib/cpp).
105 Changed interface of Stdpp.line_of_loc: now return also a string: the name
106 of the real input file name.
107 - [14 Oct 02] Fixed bug in normal syntax (pa_o.cmo): the constructors
108 with currification of parameters (C x y) were accepted.
109 - [14 Oct 02] Fixed many problems of make under Windows (in particular if
110 installations directories contain spaces).
111 - [11 Oct 02] In ocaml syntax (pa_o.cmo), fixed 3 bugs (or incompatibilities
112 with the ocaml yacc version of the compiler): 1/ "ref new foo" was
113 interpreted as "ref;; new foo" instead of "ref (new foo)" 2/ unary
114 minuses did not work correctly (nor in quotation of syntax trees), in
115 particular "-0.0" 3/ "begin end" was a syntax error, instead of being "()".
116 - [Sep-Oct 02] Many changes and improvements in Scheme syntax.
117 - [07 Oct 02] Added definition of Pcaml.type_declaration which is
118 now visible in the interface, allowing to change the type declarations.
119 - [07 Oct 02] Added Pcaml.syntax_name to allow syntax extensions to test
120 it and take different decision. In revised syntax, its value is "Revised",
121 in normal syntax "OCaml" and in Scheme syntax "Scheme".
122 - [03 Oct 02] Added lexing of '\xHH' where HH is hexadecimal number.
123 - [01 Oct 02] In normal syntax (camlp4o), fixed problem of lexing
124 comment: (* bleble'''*)
125 - [23 Sep 02] Fixed bug: input "0x" raised Failure "int_of_string"
126 without location (syntaxes pa_o and pa_r).
127 - [14 Sep 02] Added functions Grammar.iter_entry and Grammar.fold_entry
128 to iterate a grammar entry and transitively all the entries it calls.
129 - [12 Sep 02] Added "Pcaml.rename_id", a hook to allow parsers to give
130 ability to rename their identifiers. Called in Scheme syntax (pa_scheme.ml)
131 when generating its identifiers.
132 - [09 Sep 02] Fixed bug under toplevel, the command:
133 !Toploop.parse_toplevel_phrase (Lexing.from_buff "1;;");;
134 failed "End_of_file".
135 - [06 Sep 02] Added "Pcaml.string_of". Combined with Pcaml.pr_expr,
136 Pcaml.pr_patt, and so on, allow to pretty print syntax trees in string.
137 E.g. in the toplevel:
139 # Pcaml.string_of Pcaml.pr_expr <:expr< let x = 3 in x + 2 >>;;
140 - : string = "let x = 3 in x + 2"
145 - [24 Jul 02] Added Scheme syntax: pa_scheme.ml, camlp4sch.cma (toplevel),
149 -----------------------
151 - [12 Jul 02] Better treatment of comments in option -cip (add comments
152 in phrases) for both printers pr_o.cmo (normal syntax) and pr_r.cmo
153 (revised syntax); added comments before let binding and class
154 structure items; treat comments inside sum and record type definitions;
155 the option -tc is now deprecated and equivalent to -cip.
156 - [13 Jun 02] Added pa_lefteval.cmo: add let..in expressions to guarantee
157 left evaluation of functions parameters, t-uples, and so on (instead of
158 the default non-specified-but-in-fact-right-to-left evaluation).
159 - [06 Jun 02] Changed revised syntax (pa_r) of variants types definition;
160 (Jacques Garrigue's idea):
161 old syntax new syntax
163 [| < ... |] [ < ... ]
164 [| > ... |] [ > ... ]
165 This applies also in predefined quotations of syntax tree for types
167 - [05 Jun 02] Added option -ss in pr_o.cmo: print with double semicolons;
168 and the option -no_ss is now by default.
169 - [30 May 02] Improved SML syntax (pa_sml).
170 - [30 May 02] Changed the AST for the "with module" construct (was with
171 type "module_type"; changed into type "module_expr").
172 - [26 May 02] Added missing abstract module types.
173 - [21 Apr 02] Added polymorphic types for polymorphic methods:
174 revised syntax (example): ! 'a 'b . type
175 ctyp quotation: <:ctyp< ! $list:pl$ . $t$ >>
176 - [17 Apr 02] Fixed bug: in normal syntax (pa_o.cmo) made a parse error on
177 the "dot" on (in interface file file):
178 class c : a * B.c -> object val x : int end
179 - [03 Apr 02] Fixed bug: (* "(*" *) resulted in "comment not terminated".
180 - [03 Apr 02] Fixed incompatibility with ocaml: ''' and '"' must be
181 displayed as '\'' and '\"' in normal syntax printer (pr_o.cmo).
182 - [03 Apr 02] When there are several tokens parsed together (locally LL(n)),
183 the location error now highlights all tokens, resulting in a more clear
184 error message (e.g. "for i let" would display "illegal begin of expr"
185 and highlight the 3 tokens, not just "for").
186 - [30 Mar 02] Added pa_extfold.cmo extending pa_extend.cmo by grammar
187 symbols FOLD0 and FOLD1. Work like LIST0 and LIST1 but have two initial
188 parameters: a function of type 'a -> 'b -> 'b doing the fold and an
189 initial value of type 'b. Actually, LIST0 now is like
190 FOLD0 (fun x y -> x :: y) []
191 with an reverse of the resulting list.
192 - [20 Mar 02] Fixed problem: when running a toplevel linked with camlp4
193 as a script, the camlp4 welcome message was displayed.
194 - [14 Mar 02] The configure shell and the program now test the consistency
195 of OCaml and Camlp4. Therefore 1/ if trying to compile this version with
196 an incompatible OCaml version or 2/ trying to run an installed Camlp4 with
197 a incompatible OCaml version: in both cases, camlp4 fails.
198 - [14 Mar 02] When make opt.opt is done, the very fast version is made for
199 the normal syntax ("compiled" version). The installed camlp4o.opt is that
201 - [05 Mar 02] Changed the conversion to OCaml syntax tree for <:expr< x.val >>
202 and <:expr< x.val := e >> which generates now the tree of !x and x := e,
203 no more x.contents and x.contents <- e. This change was necessary because
204 of a problem if a record has been defined with a field named "contents".
206 - [16 Feb 02] Changed interface of grammars: the token type is now
207 customizable, using a new lexer type Token.glexer, parametrized by
208 the token type, and a new functor GMake. This was accompanied by
209 some cleanup. Become deprecated: the type Token.lexer (use Token.glexer),
210 Grammar.create (use Grammar.gcreate), Unsafe.reinit_gram (use
211 Unsafe.gram_reinit), the functor Grammar.Make (use Grammar.GMake).
212 Deprecated means that they are kept during some versions and removed
214 - [06 Feb 02] Added missing infix "%" in pa_o (normal syntax).
215 - [06 Feb 02] Added Grammar.print_entry printing any kind of (obj) entry
216 and having the Format.formatter as first parameter (Grammar.Entry.print
217 and its equivalent in functorial interface call it).
218 - [05 Feb 02] Added a flag Plexer.no_quotations. When set to True, the
219 quotations are no more lexed in all lexers built by Plexer.make ()
220 - [05 Feb 02] Changed the printing of options so that the option -help
221 aligns correctly their documentation. One can use now Pcaml.add_option
222 without having to calculate that.
223 - [05 Feb 02] pr_r.cmo: now the option -ncip (no comments in phrases) is
224 by default, because its behaviour is not 100% sure. An option -cip has
225 been added to set it.
226 - [03 Feb 02] Added function Stdpp.line_of_loc returning the line and
227 columns positions from a character location and a file.
228 - [01 Feb 02] Fixed bug in token.ml: the location function provided by
229 lexer_func_of_parser, lexer_func_of_ocamllex and make_stream_and_location
230 could raise Invalid_argument "Array.make" for big files if the number
231 of read tokens overflows the maximum arrays size (Sys.max_array_length).
232 The bug is not really fixed: in case of this overflow, the returned
233 location is (0, 0) (but the program does not fail).
234 - [28 Jan 02] Fixed bug in pa_o when parsing class_types. A horrible hack
235 had to be programmed to be able to treat them correctly.
236 - [28 Jan 02] Fixed bug in OCaml toplevel when loading camlp4: the directives
237 were not applied in the good order.
238 - [26 Jan 02] The printer pr_extend.cmo try now also to rebuild GEXTEND
239 statements (before it tried only the EXTEND).
240 - [23 Jan 02] The empty functional stream "fstream [: :]" is now of type
241 'a Fstream.t thanks to the new implementation of lazies allowing to
242 create polymorphic lazy values.
243 - [11 Jan 02] Added a test in grammars using Plexer that a keyword is not
244 used also as parameter of a LIDENT or a UIDENT.
245 - [04 Jan 02] Fixed bug in pa_sml (SML syntax): the function definitions
246 with several currified parameters did not work. It works now, but the
247 previous code was supposed to treat let ("fun" in SML syntax) definitions
248 of infix operators, what does not work any more now.
249 - [04 Jan 02] Alain Frisch's contribution:
250 Added pa_ocamllex.cma, syntax for ocamllex files. The command:
251 camlp4 pa_ocamllex.cmo pr_o.cmo -ocamllex -impl foo.mll > foo.ml
252 does the same thing as:
254 Allow to compile directly mll files. Without option -ocamllex, allow
255 to insert lex rules in a ml file.
256 - [29 Dec 01] Added variable "inter_phrases" in Pcaml, of type ref (option
257 string) to specify the string to print between phrases in pretty printers.
258 The default is None, meaning to copy the inter phrases from the source
264 - [07 Dec 01] Added Pcaml.parse_interf and Pcaml.parse_implem, hooks to
265 specify the parsers tof use, i.e. now can use other parsing technics
266 than the Camlp4 grammar system.
267 - [27 Nov 01] Fixed functions Token.eval_char and Token.eval_string which
268 returned bad values, resulting lexing of backslash sequences incompatible
269 with OCaml (e.g. "\1" returned "\001" (one character) but OCaml returns
270 the string of the two characters \ and 1).
271 - [15 Nov 01] In revised syntax, in let binding in sequences, the "in"
272 can be replaced by a semicolon; the revised syntax printer pr_r.cmo
273 now rather prints a semicolon there.
274 - [07 Nov 01] Added the ability to use $ as token: was impossible so far,
275 because of AST quotation uses it for its antiquotation. The fix is just
276 a little (invisible) change in Plexer.
277 - [05 Nov 01] Added option -tc (types comment) when using pr_o or pr_r
278 try to print comments inside sum and record types like they are in
279 the source (not by default, because may work incorrectly).
280 - [05 Nov 01] Added option -ca (comment after) when using pr_o or pr_r:
281 print ocamldoc comments after the declarations, when they are before.
282 - [04 Nov 01] Added locations for variants and labels declarations in AST
284 - [03 Nov 01] In pretty printers pr_o and pr_r, skip to next begin of line
285 when displaying the sources between phrase, to prevent e.g. the displaying
286 of the possible last comment of a sum type declaration (the other comment
287 being not displayed anyway).
288 - [24 Oct 01] Fixed incorrect locations in sequences.
289 - [24 Oct 01] Was erroneously compiled by the OCaml boot compiler instead
290 of the generated ocamlc. Fixed.
291 - [15 Oct 01] Fixed some parsing differences between pa_o and ocamlyacc:
292 in parsers, in labels.
293 - [12 Oct 01] Added missing bigarray syntax a.{b} (and Cie) in standard
299 - [09 Oct 01] Fixed bug: the token !$ did not work. Fixed and completed
300 some syntaxes of labels patterns. Added missing case in exception
301 declaration (exception rebinding).
302 - [05 Oct 01] Fixed bug in normal syntax: when defining a constructor
303 named "True" of "False" (capitalized, i.e. not like the booleans), it
305 - [04 Oct 01] Fixed some revised and quotation syntaxes in objects classes
306 and types (cleaner). Cleaned up also several parts of the parsers.
307 - [02 Oct 01] In revised syntax, the warning for using old syntax for
308 sequences is now by default. To remove it, the option -no-warn-seq
309 of camlp4r has been added. Option -warn-seq has been removed.
310 - [07 Sep 01] Included Camlp4 in OCaml distribution.
311 - [06 Sep 01] Added missing pattern construction #t
312 - [05 Sep 01] Fixed bug in pa_o: {A.B.c = d} was refused.
313 - [26 Aug 01] Fixed bug: in normal and revised syntaxes, refused -1.0
314 (minus float) as pattern.
315 - [24 Aug 01] Fixed bug: (a : b :> c) and ((a : b) :> c) were parsed
317 - [20 Aug 01] Fixed configure script for Windows configuration.
318 - [10 Aug 01] Fixed bug: <:expr< 'a' >> did not work because of a typing
320 - [10 Aug 01] Fixed bug in compilation process under Windows: the use of
321 the extension .exe was missing in several parts in Makefiles and shell
323 - [09 Aug 01] Changed message error in grammar: in the case when the rule
324 is: ....; tok1; tok2; .. tokn; ... (n terminal tokens following each other),
325 where the grammar is locally LL(n), it displays now:
326 tok1 tok2 .. tokn expected
329 because "tok1" can be correct in the input, and in this case, the message
330 underscored the tok1 and said "tok1 expected".
331 - [07 Aug 01] When camlp4r.cma is loaded in the toplevel, the results are
332 now displayed in revised syntax.
333 - [04 Aug 01] Added syntax "declare..end" in quotations class_str_item and
334 class_sig_item to be able to generate several items from one only item
335 (like in str_item and sig_item).
340 - [21 Jul 01] Fixed bug: <:expr< { l = x } >> was badly built and resulted
342 - [13 Jul 01] Fixed bug: did not accept floats in patterns.
343 - [11 Jul 01] Added function Pcaml.top_printer to be able to use the
344 printers Pcaml.pr_expr, Pcaml.pr_patt, and so on for the #install_printer
345 of OCaml toplevel. Ex:
346 let f = Pcaml.top_printer Pcaml.pr_expr;;
349 - [24 Jun 01] In grammars, added symbol ANY, returning the current token,
351 - [24 Jun 01] In grammars, a rule list of the form [ s1 | s2 | .. | sn ]
352 is interpreted as [ x = s1 -> x | x = s2 -> x | .. x = sn -> x ]
353 instead of [ _ = s1 -> () | _ = s2 -> () .. ]
354 - [24 Jun 01] Moved the functions [Plexer.char_of_char_token] and
355 [Plexer.string_of_string_token] into module [Token] with names
356 [Token.eval_char] and [Token.eval_string].
357 - [22 Jun 01] Added warning when using old syntax for sequences, while
358 and do (do..return, do..done) in predefined quotation expr.
359 - [22 Jun 01] Changed message for unbound quotations (more clear).
361 Camlp4 Version 3.01.6:
362 ----------------------
364 - [22 Jun 01] Changed the module Pretty into Spretty.
365 - [21 Jun 01] Camlp4 can now be compiled even if OCaml is not installed:
366 in the directory "config", the file "configure_batch" is a possibility
367 to configure the compilation (alternative of "configure" of the top
368 directory) and has a parameter "-ocaml-top" to specify the OCaml top
369 directory (relative to the camlp4/config directory).
370 - [21 Jun 01] The interactive "configure" now tests if the native-code
371 compilers ocamlc.opt and ocamlopt.opt are accessible and tell the
372 Makefile to preferably use them if they are.
373 - [16 Jun 01] The syntax tree for strings and characters now represent their
374 exact input representation (the node for characters is now of type string,
375 no more char). For example, the string "a\098c" remains "a\098c" and is
376 *not* converted into (the equivalent) "abc" in the syntax tree. The
377 convertion takes place when converting into OCaml tree representation.
378 This has the advantage that the pretty print now display them as they
379 are in the input file. To convert from input to real representation
380 (if needed), two functions have been added: Plexer.string_of_string_token
381 and Plexer.char_of_char_token.
382 - [10 Jun 01] In revised syntax, added ability to write {foo x = y} as short
383 form for {foo = fun x -> y}.
384 - [08 Jun 01] Completed missing cases in pa_extfun.cmo for variants.
385 - [06 Jun 01] Completed missing cases in abstract syntax tree and in normal
386 syntax parser pa_o.ml (about classes).
387 - [06 Jun 01] Fixed bug in pa_o.cmo (parser of normal syntax): (~~) did not
388 work, and actually all prefix operators between parentheses.
390 Camlp4 Version 3.01.5:
391 ----------------------
393 - [04 Jun 01] Fixed bug: when using "include" in a structure item the rest
394 of the structure was lost.
395 - [31 May 01] Added ability to user #load and #directory inside ml or mli
396 files to specify a cmo file to be loaded (for syntax extension) or the
397 directory path (like option -I). Same semantics than in toplevel.
398 - [29 May 01] The name of the location variable used in grammars (action
399 parts of the rules) and in the predefined quotations for OCaml syntax
400 trees is now configurable in Stdpp.loc_name (string reference). Added also
401 option -loc to set this variable. Default: loc.
402 - [26 May 01] Added functional streams: a library module Fstream and a syntax
403 kit: pa_fstream.cmo. Syntax:
404 streams: fstream [: ... :]
405 parsers: fparser [ [: ... :] -> ... | ... ]
406 - [25 May 01] Added function Token.lexer_func_of a little bit more general
407 than Token.lexer_func_of_parser.
409 Camlp4 Version 3.01.4:
410 ----------------------
412 - [20 May 01] Fixed bug: pr_rp and pr_op could generate bound variables
413 resulting incorrect program:
414 (e.g. fun s -> parser [: `_; x :] -> s x was printed:
415 fun s -> parser [: `_; s :] -> s s)
416 - [19 May 01] Small improvement in pretty.ml resulting a faster print (no
417 more stacked HOVboxes which printers pr_r and pr_o usually generate in
418 expr, patt, ctyp, etc.)
419 - [18 May 01] Added [lexer_func_of_parser] and [lexer_func_of_ocamllex]
420 in module [Token] to create lexers functions from char stream parsers
421 or from [ocamllex] lexers.
422 - [16 May 01] Pretty printing with pr_r.cmo (revised syntax) now keep
423 comments inside phrases.
424 - [15 May 01] Changed pretty printing system, using now new extensible
426 - [15 May 01] Added library module Extfun for extensible functions,
427 syntax pa_extfun, and a printer pr_extfun.
428 - [12 May 01] Fixed bug: missing cases in pr_o and pr_r for in cases of
429 "for", "while", and some other expressions, when between parentheses.
431 Camlp4 Version 3.01.3:
432 ----------------------
434 - [04 May 01] Put back the syntax "do ... return ..." in predefined
435 quotation "expr", to be able to compile previous programs. Work
436 only if the quotation is in position of expression, not in pattern.
437 - [04 May 01] Added lisp syntax pa_lisp.cmo (not terminated).
438 - [01 May 01] Fixed bug: in toplevel, in case of syntax error in #use,
439 the display was incorrect: it displayed the input, instead of the
442 Camlp4 Version 3.01.2:
443 ----------------------
445 - [27 Apr 01] Added variable Grammar.error_verbose and option -verbose of
446 command camlp4 to display more information in case of parsing error.
447 - [27 Apr 01] Fixed bug: the locations in sequences was not what expected
448 by OCaml, resulting on bad locations displaying in case of typing error.
449 - [27 Apr 01] Fixed bug: in normal syntax, the sequence was parsed
450 of left associative instead of right associative, resulting bad pretty
453 Camlp4 Version 3.01.1:
454 ----------------------
456 - [19 Apr 01] Added missing new feature "include" (structure item).
457 - [17 Apr 01] Changed revised syntax of sequences. Now:
458 do { expr1; expr2 ..... ; exprn }
459 for patt = expr to/downto expr do { expr1; expr2 ..... ; exprn }
460 while expr do { expr1; expr2 ..... ; exprn }
461 * If holding a "let ... in", the scope applies up to the end of the sequence.
462 * The old syntax "do .... return ..." is still accepted.
463 * In expr quotation, it is *not* accepted. To ensure backward
464 compatibility, use ifdef NEWSEQ, which answers True from this version.
465 * The printer pr_r.cmo by default prints with this new syntax.
466 * To print with old syntax, use option -old_seq.
467 * To get a warning when using old syntax, use option -warn_seq.
472 - [5 Mar 01] In pa_o.ml fixed problem, did not parse:
473 class ['a, 'b] cl a b : ['a, 'b] classtype
474 - [9 Oct 00] Raise now Stream.Error when parsing with an empty entry (meaning
475 that the user probably forgot to initialize it).
476 - [21 Jul 00] Fixed (pr_o.cmo) pb of bad printing of
477 let (f : unit -> int) = fun () -> 1
478 - [10 Jun, 21 Jul 00] Added Pcaml.sync to synchronize after syntax error in
480 - [24 May 00] Changed the "make opt", returning to what was done in the
481 previous releases, i.e. just the compilation of the library (6 files).
482 The native code compilation of "camlp4o" and "camlp4r" are not absolutely
483 necessary and can create problems in some systems because of too long code.
484 The drawbacks are more important than the advantages.
485 - [19 May 00] Changed option -split_gext (when pa_extend.cmo is loaded) into
486 -split_ext: it applies now also for non functorial grammars (extended by
487 EXTEND instead of GEXTEND).
488 - [12 May 00] Fixed problem in pr_rp.cmo and pr_op.cmo: the pretty printing
489 of the construction "match x with parser" did not work (because of the
490 type constraint "Stream.t _" added some versions ago).
495 - [Apr 19, 00] Added "pa_olabl" for labels with old Olabl syntax.
496 - [Apr 18, 00] Make opt now builds camlp4o.opt and camlp4r.opt
497 - [Apr 17, 00] Added support for labels and variants.
498 - [Mar 28, 00] Improved the grammars: now the rules starting with n
499 terminals are locally LL(n), i.e. if any of the terminal fails, it is
500 not Error but just Failure. Allows to write the Ocaml syntax case:
503 with the problem of "( - )" as:
507 after factorization of the "(", the rule "-"; ")" is locally LL(2): it
508 works for this reason. In the previous implementation, a hack had to be
511 To allow this, the interface of "Token" changed. The field "tparse" is
512 now of type "pattern -> option (Stream.t t -> string)" instead of
513 "pattern -> Stream.t t -> string". Set it to "None" for standard pattern
514 parsing (or if you don't know).
519 - [Nov 23, 99] Changed the module name Config into Oconfig, because of
520 conflict problem when applications want to link with the module Config of
527 - [Jun 25, 99] Added missing case in "pr_depend.cmo": pattern A.B.C.
528 - [Jun 5, 99] Fixed in "pr_depend.ml" case expression "Foo.Bar" displaying a
529 bad dependency with file "bar.ml" if existed. And changed "pa_r.ml"
530 (revised syntax parsing) to generate a more logical ast for case
532 - [Apr 29, 99] Added missing cases in "pr_o.cmo" and in "pr_depend.cmo".
533 - [Mar 11, 99] Added missing cases in "pr_depend.cmo".
534 - [Mar 9, 99] Added missing case in pr_depend.ml.
537 - [Sep 10, 99] Updated from current Ocaml new interfaces.
538 - [Jul 9, 99] Added stream type constraint in pa_oop.ml to reflect the same
540 - [Jun 24, 99] Added missing "constraint" construction in types
541 - [Jun 15, 99] Added option -I for command "mkcamlp4".
542 - [May 14, 99] Added man pages (links) for camlp4o, camlp4r, mkcamlp4, ocpp
543 - [May 10, 99] Added shell script "configure_batch" in directory "config".
544 - [May 10, 99] Changed LICENSE to BSD.
545 - [Apr 29, 99] Added "ifdef" for mli files.
546 - [Apr 11, 99] Changed option "-no_cp" into "-sep" in pr_r.cmo and pr_o.cmo.
547 - [Apr 11, 99] Fixed (old) bug: too long strings where bad pretty printed.
548 - [Mar 24, 99] Added missing stream type constraint for parsers.
549 - [Mar 17, 99] Changed template Makefile to use ocamlc.opt and ocamlopt.opt
550 by default, instead of ocamlc and ocamlopt.
551 - [Mar 9, 99] Added ifndef in pa_ifdef.ml.
552 - [Mar 7, 99] Completed and fixed some cases in pr_extend.ml.
558 - [Feb 27, 99] Fixed 2 bugs, resulting of incorrect Ocaml parsing of the
559 program example: "type t = F(B).t"
560 - [Jan 30, 99] Fixed bug "pa_op.ml", could not parse "parser | [<>] -> ()".
561 - [Jan 16, 99] Added "define" and "undef" in "pa_ifdef.cmo".
562 - [Dec 22, 98] Fixed precedence of "!=" in Ocaml syntax
565 - [Mar 4, 99] Added pr_depend.cmo for printing file dependencies.
566 - [Dec 28, 98] Fixed pretty printing of long strings starting with spaces;
567 used to display "\\n<spaces>..." instead of "<spaces>\\n...".
570 - [Feb 19, 99] Sort command line argument list in reverse order to
571 avoid argument names conflicts when adding arguments.
574 - [Feb 26, 99] Started extensions for Olabl: directory "lablp4" and some
575 changes in MLast. Olabl programs can be preprocessed by:
576 camlp4 pa_labl.cma pr_ldump.cmo
579 - Use of pr_depend.cmo instead of ocamldep for dependencies.
585 * Big change: the type for tokens and tokens patterns is now (string * string)
586 the first string being the constructor name and the second its possible
587 parameters. No change in EXTEND statements using Plexer. But lexers
589 - a supplementary parameter "tparse" to specify how to parse token
591 - fields "using" and "removing" replacing "add_keyword" and
593 See the file README-2.01 for how to update your programs and the interface
597 * The function "keywords" have been replaced by "tokens". The equivalent
598 of the old statement:
603 Missing features added
604 * Added "lazy" statement (pa_r.cmo, pa_o.cmo, pr_r.cmo, pr_o.cmo)
605 * Added print "assert" statement (pr_o.cmo, pr_r.cmo)
606 * Added parsing of infix operators like in Ocaml (e.g. |||) in pa_o.cmo
609 * Added "make scratch"
610 * Changed Makefile. No more "make T=../", working bad in some systems.
611 * Some changes to make compilation in Windows 95/98 working better (thanks
612 to Patricia Peratto).
615 * Added quotations for classes and objects (q_MLast.ml)
616 * Added accessible entries in module Pcaml (class_type, class_expr, etc.)
617 * Changed classes and objects types in definition (module MLast)
620 * Some adds in pa_sml.cmo. Thanks to Franklin Chen.
621 * Added option "-no_cp" when "pr_o.cmo" or "pr_r.cmo" is loaded: do
622 not print comments between phrases.
623 * Added option "-split_gext" when "pa_extend.cmo" is loaded: split GEXTEND
624 by functions to turn around a PowerPC problem.
627 * Fixed pa_r.cmo, pa_o.cmo to parse, and pr_r.cmo, pr_o.cmo to print "(x:#M.c)"
628 * Fixed printing pr_o.cmo of "(a.b <- 1)::1"
629 * Extended options with parameters worked only when the parameter was sticked.
631 camlp4o pr_o.cmo -l120 foo.ml
633 camlp4o pr_o.cmo -l 120 foo.ml
638 * Designation "righteous" has been renamed "revised".
639 * Added class and objects in Ocaml printing (pr_o.cmo), revised parsing
640 (pa_r.cmo) and printing (pr_r.cmo).
641 * Fixed bug in Ocaml syntax: let _, x = 1, 2;; was refused.
643 Camlp4 Version 2.00--1:
644 -----------------------
646 * Added classes and objects in Ocaml syntax (pa_o.cmo)
647 * Fixed pr_r.cmo et pr_r.cmo which wrote on stdout, even when option -o
649 Camlp4 Version 2.00--:
650 ----------------------
652 * Adapted for Ocaml 2.00.
653 * No objects and classes in this version.
655 * Added "let module" parsing and printing.
656 * Added arrays patterns parsing and printing.
657 * Added records with "with" "{... with ...}" parsing and printing
659 * Added # num "string" in plexer (was missing).
660 * Fixed bug in pr_o.cmo: module A = B (C);; was printed module A = B C;;
661 * Added "pa_sml.cmo", SML syntax + "lib.sml"
662 * Fixed bug in pa_r.ml and pa_o.ml: forgot to clear let_binding
663 * Changed Plexer: unknown keywords do not raise error but return Tterm
664 * q_MLast.cmo: suppressed <:expr< [$list:el$] >> (cannot work)
665 * Added option "-no_ss" (no ;;) when "pr_o.cmo" loaded
666 * Many changes and bug fixing in pretty printing pr_o.cmo and pr_r.cmo
667 * Command ocpp works now without having to explicitely load
668 "/usr/local/lib/ocaml/stdlib.cma" and
669 "/usr/local/lib/camlp4/gramlib.cma"
671 * Fixed problem of pretty print "&" and "or" in normal and righteous syntaxes
672 * Added missing statement "include" in signature item in normal and righteous
674 * Changed precedence of ":=" and "<-" in normal syntax (pa_o et pr_o):
675 now before "or", like in Ocaml compiler.
676 * Same change in righteous syntax, by symmetry.
678 Camlp4 Version 1.07.2:
679 ----------------------
681 Errors and missings in normal and righteous syntaxes.
683 * Added forgotten syntax (righteous): type constraints in class type fields.
684 * Added missing syntax (normal): type foo = bar = {......}
685 * Added missing syntax (normal): did not accept separators before ending
686 constructions (many of them).
687 * Fixed bug: "assert false" is now of type 'a, like in Ocaml.
688 * Fixed to match Ocaml feature: "\^" is "\^" in Ocaml, but just "^" in Camlp4.
689 * Fixed bug in Windows NT/95: problem in backslash before newlines in strings
691 Grammars, EXTEND, DELETE_RULE
693 * Added functorial version for grammars (started in version 1.07.1,
694 completed in this version).
695 * Added statements GEXTEND and GDELETE_RULE in pa_extend.cmo for functorial
697 * EXTEND statement is added AFTER "top" instead of LEVEL "top" (because
698 of problems parsing "a; EXTEND...")
699 * Added ability to have expressions (in antiquotation form) of type string in
700 EXTEND after keywords "LIDENT", "UIDENT", "IDENT", "ANTIQUOT", "INT" as
701 in others constructions inside EXTEND.
702 * A grammar rule hidden by another is not deleted but just masked. DELETE_RULE
703 will restore the old version.
704 * DELETE_RULE now raises Not_found if no rule matched.
705 * Fixed bug: DELETE_RULE did not work when deleting a rule which is a prefix of
707 * Some functions for "system use" in [Grammar] become "official":
708 [Entry.obj], [extend], [delete_rule].
710 Command line, man page
712 * Added option -o: output on file instead of standard output, necessary
713 to allow compilation in Windows NT/95 (in fact, this option exists since
714 1.07.1 but forgotten in its "changes" list).
715 * Command line option -help more complete.
716 * Updated man page: camlp4 options are better explained.
717 * Fixed bug: "camlp4 [other-options] foo.ml" worked but not
718 "camlp4 foo.ml [other-options]".
719 * Fixed bug: "camlp4 foo" did not display a understandable error message.
723 * Changes in compilation process in order to try to make it work better for
724 Windows NT under Cygnus.
728 * Added [Pcaml.add_option] for adding command line options.
730 Camlp4 Version 1.07.1:
731 ----------------------
733 * Added forgotten syntax in pr_o: type x = y = A | B
734 * Fixed bug negative floats parsing in pa_o => error while pretty printing
735 * Added assert statement and option -noassert.
736 * Environment variable CAMLP4LIB to change camlp4 library directory
737 * Grammar: empty rules have a correct location instead of (-1, -1)
738 * Compilation possible in Windows NT/95
739 * String constants no more shared while parsing Ocaml
740 * Fixed bug in antiquotations in q_MLast.cmo (bad errors locations)
741 * Fixed bug in antiquotations in q_MLast.cmo (EOI not checked)
742 * Fixed bug in Plexer: could not create keywords with iso 8859 characters
747 * Changed version number + configuration script
748 * Added iso 8859 uppercase characters for uidents in plexer.ml
749 * Fixed bug factorization IDENT in grammars
750 * Fixed bug pr_o.cmo was printing "declare"
751 * Fixed bug constructor arity in Ocaml syntax (pa_o.cmo).
752 * Changed "lazy" into "slazy".
753 * Completed pa_ifdef.cmo.
758 * Adapted to Ocaml 1.06.
759 * Changed version number to match Ocaml's => 1.06 too.
760 * Deleted module Gstream, using Ocaml's Stream.
761 * Generate different AST for C(x,y) and C x y (change done in Ocaml's compiler)
762 * No more message "Interrupted" in toplevel in case of syntax error.
763 * Added flag to suppress warnings while extending grammars.
764 * Completed some missing statements and declarations (objects)
765 * Modified odyl implementation; works better
766 * Added ability to extend command line specification
767 * Added "let_binding" as predefined (accessible) entry in Pcaml.
768 * Added construction FUNCTION in EXTEND statement to call another function.
769 * Added some ISO-8859-1 characters in lexer identifiers.
770 * Fixed bug "value x = {val = 1};" (righteous syntax)
771 * Fixed bug "open A.B.C" was interpreted as "open B.A.C"
772 * Modified behavior of "DELETE_RULE": the complete rule must be provided
773 * Completed quotations MLast ("expr", "patt", etc) to accept whole language
774 * Renamed "LIKE" into "LEVEL" in grammar EXTEND
775 * Added "NEXT" as grammar symbol in grammar EXTEND
776 * Added command "mkcamlp4" to make camlp4 executables linked with C code
777 * Added "pr_extend.cmo" to reconstitute EXTEND instructions
784 * To compile camlp4, it is no more necessary to have the sources of the
785 Objective Caml compiler available. It can be compiled like any other
786 Objective Caml program.
788 --- Options of "camlp4"
790 * Added option -where: "camlp4 -where" prints the name of the standard
791 library directory of Camlp4 and exit. So, the ocaml toplevel and the
792 compiler can use the option:
795 * Added option -nolib to not search for objects files in the installed
796 library directory of Camlp4.
798 --- Interface of grammar library modules
800 * The function Grammar.keywords returns now a list of pairs. The pair is
801 composed of a keyword and the number of times it is used in entries.
803 * Changed interface of Token and Grammar for lexers, so user lexers have
806 --- New features in grammars
808 * New instruction "DELETE_RULE" provided by pa_extend.cmo to delete rules.
810 DELETE_RULE Pcaml.expr: "if" END;
811 deletes the "if" instruction of the language.
813 * Added the ability to parse some specific integer in grammars: a possible
814 parameter to INT, like the ones for LIDENT and UIDENT.
816 * In instruction EXTEND, ability to omit "-> action", default is "-> ()"
818 * Ability to add antiquotation (between $'s) as symbol rule, of type string,
819 interpreted as a keyword, in instruction EXTEND.
821 * Ability to put entries with qualified names (Foo.bar) in instruction EXTEND.
825 * The module Ast has been renamed MLast. The quotation expander "q_ast.cmo"
826 has been renamed "q_MLast.cmo".
828 * Quotation expanders are now of two kinds:
829 - The "classical" type for expanders returning a string. These expanders
830 have now a supplementary parameter: a boolean value set to "True"
831 when the quotation is in a context of an expression an to "False"
832 when the quotation is in a context of a pattern. These expanders,
833 returning strings which are parsed afterwards, may work for some
834 language syntax and/or language extensions used (e.g. may work for
835 Righteous syntax and not for Ocaml syntax).
836 - A new type of expander returning directly syntax trees. A pair
837 of functions, for expressions and for patterns must be provided.
838 These expanders are independant from the language syntax and/or
841 * The predefined quotation expanders "ctyp_", "patt_" and "expr_" has
842 been deleted; one can use "ctyp", "patt", and "expr" in position of
843 pattern or expression.
845 --- Ocaml and Righteous syntaxes
847 * Fixed bug: "open Foo.Bar" was converted (pr_dump.cmo) into "open Bar.Foo"
849 * Corrected behavior different from Ocaml's: "^" and "@" were at the same
850 level than "=": now, like Ocaml, they have a separated right associative
853 --- Grammars behavior
855 * While extending entries: default position is now "extension of the
856 first level", instead of "adding a new level at the end".
858 * Another Change: in each precedence level, terminals are inserted before
859 other symbols (non terminals, lists, options, etc), LIDENT "foo" before
860 LIDENT (alone) and UIDENT "foo" before UIDENT (alone). New rules not
861 factorizable are now inserted before the other rules.
863 * Changed algorithm of entries parsing: each precedence level is tested
864 against the stream *before* its next precedences levels (instead of
866 EXTEND e: [[ LIDENT "a" -> "xxx" ] | [ i = LIDENT -> i ]]; END;
867 Now, parsing the entry e with the string "a" returns "xxx" instead of "a"
869 * Less keywords in instruction EXTEND (LEFTA, LIDENT, etc), which can be
870 used now as normal identifiers.
872 * When inserting a new rule, a warning appears if a rule with the
873 same production already existed (it is deleted).
875 * Parse error messages (Gstream.Error) are formatted => spaces trigger
876 Format.print_space and newlines trigger Format.force_newline.
882 * Possible creation of native code library (make opt)
884 * Ocaml and Righteous Syntax more complete
886 * Added pa_ru.cmo for compiling sequences of type unit (Righteous)
889 - No more quotation long_id
890 - Antiquotations for identifiers more simple
892 * Lot of small changes
898 * First distributed version