summaryrefslogtreecommitdiffstats
path: root/camlp4/CHANGES
blob: d27b1bf64679d74c59d94a4fcdd20b6067b8de3c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
Camlp4 Version 3.04+5
---------------------

- [01 Fev 02] Fixed bug in token.ml: the location function provided by
  lexer_func_of_parser, lexer_func_of_ocamllex and make_stream_and_location
  could raise Invalid_argument "Array.make" for big files if the number
  of read tokens overflows the maximum arrays size (Sys.max_array_length).
  The bug is not really fixed: in case of this overflow, the returned
  location is (0, 0) (but the program does not fail).
- [28 Jan 02] Fixed bug in pa_o when parsing class_types. A horrible hack
  had to be programmed to be able to treat them correctly.
- [28 Jan 02] Fixed bug in OCaml toplevel when loading camlp4: the directives
  were not applied in the good order.
- [26 Jan 02] The printer pr_extend.cmo try now also to rebuild GEXTEND
  statements (before it tried only the EXTEND).
- [23 Jan 02] The empty functional stream "fstream [: :]" is now of type
  'a Fstream.t thanks to the new implementation of lazies allowing to
  create polymorphic lazy values.
- [11 Jan 02] Added a test in grammars using Plexer that a keyword is not
  used also as parameter of a LIDENT or a UIDENT.
- [04 Jan 02] Fixed bug in pa_sml (SML syntax): the function definitions
  with several currified parameters did not work. It works now, but the
  previous code was supposed to treat let ("fun" in SML syntax) definitions
  of infix operators, what does not work any more now.
- [04 Jan 02] Alain Frisch's contribution:
  Added pa_ocamllex.cma, syntax for ocamllex files. The command:
      camlp4 pa_ocamllex.cmo pr_o.cmo -ocamllex -impl foo.mll > foo.ml
  does the same thing as:
      ocamllex foo.mll
  Allow to compile directly mll files. Without option -ocamllex, allow
  to insert lex rules in a ml file.
- [29 Dec 01] Added variable "inter_phrases" in Pcaml, of type ref (option
  string) to specify the string to print between phrases in pretty printers.
  The default is None, meaning to copy the inter phrases from the source
  file.

Camlp4 Version 3.04
-------------------

- [07 Dec 01] Added Pcaml.parse_interf and Pcaml.parse_implem, hooks to
  specify the parsers tof use, i.e. now can use other parsing technics
  than the Camlp4 grammar system.
- [27 Nov 01] Fixed functions Token.eval_char and Token.eval_string which
  returned bad values, resulting lexing of backslash sequences incompatible
  with OCaml (e.g. "\1" returned "\001" (one character) but OCaml returns
  the string of the two characters \ and 1).
- [15 Nov 01] In revised syntax, in let binding in sequences, the "in"
  can be replaced by a semicolon; the revised syntax printer pr_r.cmo
  now rather prints a semicolon there.
- [07 Nov 01] Added the ability to use $ as token: was impossible so far,
  because of AST quotation uses it for its antiquotation. The fix is just
  a little (invisible) change in Plexer.
- [05 Nov 01] Added option -tc (types comment) when using pr_o or pr_r
  try to print comments inside sum and record types like they are in
  the source (not by default, because may work incorrectly).
- [05 Nov 01] Added option -ca (comment after) when using pr_o or pr_r:
  print ocamldoc comments after the declarations, when they are before.
- [04 Nov 01] Added locations for variants and labels declarations in AST
  (file MLast.mli).
- [03 Nov 01] In pretty printers pr_o and pr_r, skip to next begin of line
  when displaying the sources between phrase, to prevent e.g. the displaying
  of the possible last comment of a sum type declaration (the other comment
  being not displayed anyway).
- [24 Oct 01] Fixed incorrect locations in sequences.
- [24 Oct 01] Was erroneously compiled by the OCaml boot compiler instead
  of the generated ocamlc. Fixed.
- [15 Oct 01] Fixed some parsing differences between pa_o and ocamlyacc:
  in parsers, in labels.
- [12 Oct 01] Added missing bigarray syntax a.{b} (and Cie) in standard
  syntax (pa_o).

Camlp4 Version 3.03
-------------------

- [09 Oct 01] Fixed bug: the token !$ did not work. Fixed and completed
  some syntaxes of labels patterns. Added missing case in exception
  declaration (exception rebinding).
- [05 Oct 01] Fixed bug in normal syntax: when defining a constructor
  named "True" of "False" (capitalized, i.e. not like the booleans), it
  did not work.
- [04 Oct 01] Fixed some revised and quotation syntaxes in objects classes
  and types (cleaner). Cleaned up also several parts of the parsers.
- [02 Oct 01] In revised syntax, the warning for using old syntax for
  sequences is now by default. To remove it, the option -no-warn-seq
  of camlp4r has been added. Option -warn-seq has been removed.
- [07 Sep 01] Included Camlp4 in OCaml distribution.
- [06 Sep 01] Added missing pattern construction #t
- [05 Sep 01] Fixed bug in pa_o: {A.B.c = d} was refused.
- [26 Aug 01] Fixed bug: in normal and revised syntaxes, refused -1.0
  (minus float) as pattern.
- [24 Aug 01] Fixed bug: (a : b :> c) and ((a : b) :> c) were parsed
  identically.
- [20 Aug 01] Fixed configure script for Windows configuration.
- [10 Aug 01] Fixed bug: <:expr< 'a' >> did not work because of a typing
  problem.
- [10 Aug 01] Fixed bug in compilation process under Windows: the use of
  the extension .exe was missing in several parts in Makefiles and shell
  scripts.
- [09 Aug 01] Changed message error in grammar: in the case when the rule
  is: ....; tok1; tok2; .. tokn; ... (n terminal tokens following each other),
  where the grammar is locally LL(n), it displays now:
      tok1 tok2 .. tokn expected
  instead of just
      tok1 expected
  because "tok1" can be correct in the input, and in this case, the message
  underscored the tok1 and said "tok1 expected".
- [07 Aug 01] When camlp4r.cma is loaded in the toplevel, the results are
  now displayed in revised syntax.
- [04 Aug 01] Added syntax "declare..end" in quotations class_str_item and
  class_sig_item to be able to generate several items from one only item
  (like in str_item and sig_item).

Camlp4 Version 3.02
-------------------

- [21 Jul 01] Fixed bug: <:expr< { l = x } >> was badly built and resulted
  in a typing error.
- [13 Jul 01] Fixed bug: did not accept floats in patterns.
- [11 Jul 01] Added function Pcaml.top_printer to be able to use the
  printers Pcaml.pr_expr, Pcaml.pr_patt, and so on for the #install_printer
  of OCaml toplevel. Ex:
      let f = Pcaml.top_printer Pcaml.pr_expr;;
      #install_printer f;;
      #load "pr_o.cmo";;
- [24 Jun 01] In grammars, added symbol ANY, returning the current token,
  whichever it is.
- [24 Jun 01] In grammars, a rule list of the form [ s1 | s2 | .. | sn ]
  is interpreted as [ x = s1 -> x | x = s2 -> x | .. x = sn -> x ]
  instead of [ _ = s1 -> () | _ = s2 -> () .. ]
- [24 Jun 01] Moved the functions [Plexer.char_of_char_token] and
  [Plexer.string_of_string_token] into module [Token] with names
  [Token.eval_char] and [Token.eval_string].
- [22 Jun 01] Added warning when using old syntax for sequences, while
  and do (do..return, do..done) in predefined quotation expr.
- [22 Jun 01] Changed message for unbound quotations (more clear).

Camlp4 Version 3.01.6:
----------------------

- [22 Jun 01] Changed the module Pretty into Spretty.
- [21 Jun 01] Camlp4 can now be compiled even if OCaml is not installed:
  in the directory "config", the file "configure_batch" is a possibility
  to configure the compilation (alternative of "configure" of the top
  directory) and has a parameter "-ocaml-top" to specify the OCaml top
  directory (relative to the camlp4/config directory).
- [21 Jun 01] The interactive "configure" now tests if the native-code
  compilers ocamlc.opt and ocamlopt.opt are accessible and tell the
  Makefile to preferably use them if they are.
- [16 Jun 01] The syntax tree for strings and characters now represent their
  exact input representation (the node for characters is now of type string,
  no more char). For example, the string "a\098c" remains "a\098c" and is
  *not* converted into (the equivalent) "abc" in the syntax tree. The
  convertion takes place when converting into OCaml tree representation.
  This has the advantage that the pretty print now display them as they
  are in the input file. To convert from input to real representation
  (if needed), two functions have been added: Plexer.string_of_string_token
  and Plexer.char_of_char_token.
- [10 Jun 01] In revised syntax, added ability to write {foo x = y} as short
  form for {foo = fun x -> y}.
- [08 Jun 01] Completed missing cases in pa_extfun.cmo for variants.
- [06 Jun 01] Completed missing cases in abstract syntax tree and in normal
  syntax parser pa_o.ml (about classes).
- [06 Jun 01] Fixed bug in pa_o.cmo (parser of normal syntax): (~~) did not
  work, and actually all prefix operators between parentheses.

Camlp4 Version 3.01.5:
----------------------

- [04 Jun 01] Fixed bug: when using "include" in a structure item the rest
  of the structure was lost.
- [31 May 01] Added ability to user #load and #directory inside ml or mli
  files to specify a cmo file to be loaded (for syntax extension) or the
  directory path (like option -I). Same semantics than in toplevel.
- [29 May 01] The name of the location variable used in grammars (action
  parts of the rules) and in the predefined quotations for OCaml syntax
  trees is now configurable in Stdpp.loc_name (string reference). Added also
  option -loc to set this variable. Default: loc.
- [26 May 01] Added functional streams: a library module Fstream and a syntax
  kit: pa_fstream.cmo. Syntax:
      streams: fstream [: ... :]
      parsers: fparser [ [: ... :] -> ... | ... ]
- [25 May 01] Added function Token.lexer_func_of a little bit more general
  than Token.lexer_func_of_parser.

Camlp4 Version 3.01.4:
----------------------

- [20 May 01] Fixed bug: pr_rp and pr_op could generate bound variables
  resulting incorrect program:
  (e.g. fun s -> parser [: `_; x :] -> s x was printed:
        fun s -> parser [: `_; s :] -> s s)
- [19 May 01] Small improvement in pretty.ml resulting a faster print (no
  more stacked HOVboxes which printers pr_r and pr_o usually generate in
  expr, patt, ctyp, etc.)
- [18 May 01] Added [lexer_func_of_parser] and [lexer_func_of_ocamllex]
  in module [Token] to create lexers functions from char stream parsers
  or from [ocamllex] lexers.
- [16 May 01] Pretty printing with pr_r.cmo (revised syntax) now keep
  comments inside phrases.
- [15 May 01] Changed pretty printing system, using now new extensible
  functions of Camlp4.
- [15 May 01] Added library module Extfun for extensible functions,
  syntax pa_extfun, and a printer pr_extfun.
- [12 May 01] Fixed bug: missing cases in pr_o and pr_r for in cases of
  "for", "while", and some other expressions, when between parentheses.

Camlp4 Version 3.01.3:
----------------------

- [04 May 01] Put back the syntax "do ... return ..." in predefined
  quotation "expr", to be able to compile previous programs. Work
  only if the quotation is in position of expression, not in pattern.
- [04 May 01] Added lisp syntax pa_lisp.cmo (not terminated).
- [01 May 01] Fixed bug: in toplevel, in case of syntax error in #use,
  the display was incorrect: it displayed the input, instead of the
  file location.

Camlp4 Version 3.01.2:
----------------------

- [27 Apr 01] Added variable Grammar.error_verbose and option -verbose of
  command camlp4 to display more information in case of parsing error.
- [27 Apr 01] Fixed bug: the locations in sequences was not what expected
  by OCaml, resulting on bad locations displaying in case of typing error.
- [27 Apr 01] Fixed bug: in normal syntax, the sequence was parsed
  of left associative instead of right associative, resulting bad pretty
  printing.

Camlp4 Version 3.01.1:
----------------------

- [19 Apr 01] Added missing new feature "include" (structure item).
- [17 Apr 01] Changed revised syntax of sequences. Now:
       do { expr1; expr2 ..... ; exprn }
       for patt = expr to/downto expr do { expr1; expr2 ..... ; exprn }
       while expr do { expr1; expr2 ..... ; exprn }
  * If holding a "let ... in", the scope applies up to the end of the sequence.
  * The old syntax "do .... return ..." is still accepted.
  * In expr quotation, it is *not* accepted. To ensure backward
    compatibility, use ifdef NEWSEQ, which answers True from this version.
  * The printer pr_r.cmo by default prints with this new syntax.
  * To print with old syntax, use option -old_seq.
  * To get a warning when using old syntax, use option -warn_seq.

Camlp4 Version 3.01:
--------------------

- [5 Mar 01] In pa_o.ml fixed problem, did not parse:
       class ['a, 'b] cl a b : ['a, 'b] classtype
- [9 Oct 00] Raise now Stream.Error when parsing with an empty entry (meaning
  that the user probably forgot to initialize it).
- [21 Jul 00] Fixed (pr_o.cmo) pb of bad printing of
     let (f : unit -> int) = fun () -> 1
- [10 Jun, 21 Jul 00] Added Pcaml.sync to synchronize after syntax error in
  toplevel.
- [24 May 00] Changed the "make opt", returning to what was done in the
  previous releases, i.e. just the compilation of the library (6 files).
  The native code compilation of "camlp4o" and "camlp4r" are not absolutely
  necessary and can create problems in some systems because of too long code.
  The drawbacks are more important than the advantages.
- [19 May 00] Changed option -split_gext (when pa_extend.cmo is loaded) into
  -split_ext: it applies now also for non functorial grammars (extended by
  EXTEND instead of GEXTEND).
- [12 May 00] Fixed problem in pr_rp.cmo and pr_op.cmo: the pretty printing
  of the construction "match x with parser" did not work (because of the
  type constraint "Stream.t _" added some versions ago).

Camlp4 Version 3.00:
--------------------

- [Apr 19, 00] Added "pa_olabl" for labels with old Olabl syntax.
- [Apr 18, 00] Make opt now builds camlp4o.opt and camlp4r.opt
- [Apr 17, 00] Added support for labels and variants.
- [Mar 28, 00] Improved the grammars: now the rules starting with n
  terminals are locally LL(n), i.e. if any of the terminal fails, it is
  not Error but just Failure. Allows to write the Ocaml syntax case:
        ( operator )
        ( expr )
  with the problem of "( - )" as:
        "("; "-"; ")"
        "("; operator; ")"
        "("; expr; ")"
  after factorization of the "(", the rule "-"; ")" is locally LL(2): it
  works for this reason. In the previous implementation, a hack had to be
  added for this case.

  To allow this, the interface of "Token" changed. The field "tparse" is
  now of type "pattern -> option (Stream.t t -> string)" instead of
  "pattern -> Stream.t t -> string". Set it to "None" for standard pattern
  parsing (or if you don't know).

Camlp4 Version 2.04:
--------------------

- [Nov 23, 99] Changed the module name Config into Oconfig, because of
  conflict problem when applications want to link with the module Config of
  Ocaml.

Camlp4 Version 2.03:
--------------------

* pr_depend:
  - [Jun 25, 99] Added missing case in "pr_depend.cmo": pattern A.B.C.
  - [Jun 5, 99] Fixed in "pr_depend.ml" case expression "Foo.Bar" displaying a
    bad dependency with file "bar.ml" if existed. And changed "pa_r.ml"
    (revised syntax parsing) to generate a more logical ast for case
    "var.Mod.lab".
  - [Apr 29, 99] Added missing cases in "pr_o.cmo" and in "pr_depend.cmo".
  - [Mar 11, 99] Added missing cases in "pr_depend.cmo".
  - [Mar 9, 99] Added missing case in pr_depend.ml.

* Other:
  - [Sep 10, 99] Updated from current Ocaml new interfaces.
  - [Jul 9, 99] Added stream type constraint in pa_oop.ml to reflect the same
    change in Ocaml.
  - [Jun 24, 99] Added missing "constraint" construction in types
  - [Jun 15, 99] Added option -I for command "mkcamlp4".
  - [May 14, 99] Added man pages (links) for camlp4o, camlp4r, mkcamlp4, ocpp
  - [May 10, 99] Added shell script "configure_batch" in directory "config".
  - [May 10, 99] Changed LICENSE to BSD.
  - [Apr 29, 99] Added "ifdef" for mli files.
  - [Apr 11, 99] Changed option "-no_cp" into "-sep" in pr_r.cmo and pr_o.cmo.
  - [Apr 11, 99] Fixed (old) bug: too long strings where bad pretty printed.
  - [Mar 24, 99] Added missing stream type constraint for parsers.
  - [Mar 17, 99] Changed template Makefile to use ocamlc.opt and ocamlopt.opt
    by default, instead of ocamlc and ocamlopt.
  - [Mar 9, 99] Added ifndef in pa_ifdef.ml.
  - [Mar 7, 99] Completed and fixed some cases in pr_extend.ml.

Camlp4 Version 2.02:
--------------------

* Parsing:
  - [Feb 27, 99] Fixed 2 bugs, resulting of incorrect Ocaml parsing of the
    program example: "type t = F(B).t"
  - [Jan 30, 99] Fixed bug "pa_op.ml", could not parse "parser | [<>] -> ()".
  - [Jan 16, 99] Added "define" and "undef" in "pa_ifdef.cmo".
  - [Dec 22, 98] Fixed precedence of "!=" in Ocaml syntax

* Printing:
  - [Mar 4, 99] Added pr_depend.cmo for printing file dependencies.
  - [Dec 28, 98] Fixed pretty printing of long strings starting with spaces;
    used to display "\\n<spaces>..." instead of "<spaces>\\n...".

* Camlp4:
  - [Feb 19, 99] Sort command line argument list in reverse order to
    avoid argument names conflicts when adding arguments.

* Olabl:
  - [Feb 26, 99] Started extensions for Olabl: directory "lablp4" and some
    changes in MLast. Olabl programs can be preprocessed by:
        camlp4 pa_labl.cma pr_ldump.cmo

* Internal:
  - Use of pr_depend.cmo instead of ocamldep for dependencies.

Camlp4 Version 2.01:
--------------------

Token interface
* Big change: the type for tokens and tokens patterns is now (string * string)
  the first string being the constructor name and the second its possible
  parameters. No change in EXTEND statements using Plexer. But lexers
  have:
  - a supplementary parameter "tparse" to specify how to parse token
    from token patterns.
  - fields "using" and "removing" replacing "add_keyword" and
    "remove_keyword".
  See the file README-2.01 for how to update your programs and the interface
  of Token.

Grammar interface
* The function "keywords" have been replaced by "tokens". The equivalent
  of the old statement:
       Grammar.keywords g
  is now:
       Grammar.tokens g ""

Missing features added 
* Added "lazy" statement (pa_r.cmo, pa_o.cmo, pr_r.cmo, pr_o.cmo)
* Added print "assert" statement (pr_o.cmo, pr_r.cmo)
* Added parsing of infix operators like in Ocaml (e.g. |||) in pa_o.cmo

Compilation
* Added "make scratch"
* Changed Makefile. No more "make T=../", working bad in some systems.
* Some changes to make compilation in Windows 95/98 working better (thanks
  to Patricia Peratto).

Classes and objects
* Added quotations for classes and objects (q_MLast.ml)
* Added accessible entries in module Pcaml (class_type, class_expr, etc.)
* Changed classes and objects types in definition (module MLast)

Miscelleneous
* Some adds in pa_sml.cmo. Thanks to Franklin Chen.
* Added option "-no_cp" when "pr_o.cmo" or "pr_r.cmo" is loaded: do
  not print comments between phrases.
* Added option "-split_gext" when "pa_extend.cmo" is loaded: split GEXTEND
  by functions to turn around a PowerPC problem.

Bug fixes
* Fixed pa_r.cmo, pa_o.cmo to parse, and pr_r.cmo, pr_o.cmo to print "(x:#M.c)"
* Fixed printing pr_o.cmo of "(a.b <- 1)::1"
* Extended options with parameters worked only when the parameter was sticked.
  Ex:
     camlp4o pr_o.cmo -l120 foo.ml
  worked, but not:
     camlp4o pr_o.cmo -l 120 foo.ml

Camlp4 Version 2.00:
--------------------

* Designation "righteous" has been renamed "revised".
* Added class and objects in Ocaml printing (pr_o.cmo), revised parsing
  (pa_r.cmo) and printing (pr_r.cmo).
* Fixed bug in Ocaml syntax: let _, x = 1, 2;; was refused.

Camlp4 Version 2.00--1:
-----------------------

* Added classes and objects in Ocaml syntax (pa_o.cmo)
* Fixed pr_r.cmo et pr_r.cmo which wrote on stdout, even when option -o

Camlp4 Version 2.00--:
----------------------

* Adapted for Ocaml 2.00.
* No objects and classes in this version.

* Added "let module" parsing and printing.
* Added arrays patterns parsing and printing.
* Added records with "with" "{... with ...}" parsing and printing

* Added # num "string" in plexer (was missing).
* Fixed bug in pr_o.cmo: module A = B (C);; was printed module A = B C;;
* Added "pa_sml.cmo", SML syntax + "lib.sml"
* Fixed bug in pa_r.ml and pa_o.ml: forgot to clear let_binding
* Changed Plexer: unknown keywords do not raise error but return Tterm
* q_MLast.cmo: suppressed <:expr< [$list:el$] >> (cannot work)
* Added option "-no_ss" (no ;;) when "pr_o.cmo" loaded
* Many changes and bug fixing in pretty printing pr_o.cmo and pr_r.cmo
* Command ocpp works now without having to explicitely load
  "/usr/local/lib/ocaml/stdlib.cma" and
  "/usr/local/lib/camlp4/gramlib.cma"

* Fixed problem of pretty print "&" and "or" in normal and righteous syntaxes
* Added missing statement "include" in signature item in normal and righteous
  syntaxes
* Changed precedence of ":=" and "<-" in normal syntax (pa_o et pr_o):
  now before "or", like in Ocaml compiler.
* Same change in righteous syntax, by symmetry.

Camlp4 Version 1.07.2:
----------------------

Errors and missings in normal and righteous syntaxes.

* Added forgotten syntax (righteous): type constraints in class type fields.
* Added missing syntax (normal): type foo = bar = {......}
* Added missing syntax (normal): did not accept separators before ending
  constructions (many of them).
* Fixed bug: "assert false" is now of type 'a, like in Ocaml.
* Fixed to match Ocaml feature: "\^" is "\^" in Ocaml, but just "^" in Camlp4.
* Fixed bug in Windows NT/95: problem in backslash before newlines in strings

Grammars, EXTEND, DELETE_RULE

* Added functorial version for grammars (started in version 1.07.1, 
  completed in this version).
* Added statements GEXTEND and GDELETE_RULE in pa_extend.cmo for functorial
  version.
* EXTEND statement is added AFTER "top" instead of LEVEL "top" (because
  of problems parsing "a; EXTEND...")
* Added ability to have expressions (in antiquotation form) of type string in
  EXTEND after keywords "LIDENT", "UIDENT", "IDENT", "ANTIQUOT", "INT" as
  in others constructions inside EXTEND.
* A grammar rule hidden by another is not deleted but just masked. DELETE_RULE
  will restore the old version.
* DELETE_RULE now raises Not_found if no rule matched.
* Fixed bug: DELETE_RULE did not work when deleting a rule which is a prefix of
  another rule.
* Some functions for "system use" in [Grammar] become "official":
  [Entry.obj], [extend], [delete_rule].

Command line, man page

* Added option -o: output on file instead of standard output, necessary
  to allow compilation in Windows NT/95 (in fact, this option exists since
  1.07.1 but forgotten in its "changes" list).
* Command line option -help more complete.
* Updated man page: camlp4 options are better explained.
* Fixed bug: "camlp4 [other-options] foo.ml" worked but not
  "camlp4 foo.ml [other-options]".
* Fixed bug: "camlp4 foo" did not display a understandable error message.

Camlp4's compilation

* Changes in compilation process in order to try to make it work better for
  Windows NT under Cygnus.

Miscellaneous

* Added [Pcaml.add_option] for adding command line options.

Camlp4 Version 1.07.1:
----------------------

* Added forgotten syntax in pr_o: type x = y = A | B
* Fixed bug negative floats parsing in pa_o => error while pretty printing
* Added assert statement and option -noassert.
* Environment variable CAMLP4LIB to change camlp4 library directory
* Grammar: empty rules have a correct location instead of (-1, -1)
* Compilation possible in Windows NT/95
* String constants no more shared while parsing Ocaml
* Fixed bug in antiquotations in q_MLast.cmo (bad errors locations)
* Fixed bug in antiquotations in q_MLast.cmo (EOI not checked)
* Fixed bug in Plexer: could not create keywords with iso 8859 characters

Camlp4 Version 1.07:
--------------------

* Changed version number + configuration script
* Added iso 8859 uppercase characters for uidents in plexer.ml
* Fixed bug factorization IDENT in grammars
* Fixed bug pr_o.cmo was printing "declare"
* Fixed bug constructor arity in Ocaml syntax (pa_o.cmo).
* Changed "lazy" into "slazy".
* Completed pa_ifdef.cmo.

Camlp4 Version 1.06:
--------------------

* Adapted to Ocaml 1.06.
* Changed version number to match Ocaml's => 1.06 too.
* Deleted module Gstream, using Ocaml's Stream.
* Generate different AST for C(x,y) and C x y (change done in Ocaml's compiler)
* No more message "Interrupted" in toplevel in case of syntax error.
* Added flag to suppress warnings while extending grammars.
* Completed some missing statements and declarations (objects)
* Modified odyl implementation; works better
* Added ability to extend command line specification
* Added "let_binding" as predefined (accessible) entry in Pcaml.
* Added construction FUNCTION in EXTEND statement to call another function.
* Added some ISO-8859-1 characters in lexer identifiers.
* Fixed bug "value x = {val = 1};" (righteous syntax)
* Fixed bug "open A.B.C" was interpreted as "open B.A.C"
* Modified behavior of "DELETE_RULE": the complete rule must be provided
* Completed quotations MLast ("expr", "patt", etc) to accept whole language
* Renamed "LIKE" into "LEVEL" in grammar EXTEND
* Added "NEXT" as grammar symbol in grammar EXTEND
* Added command "mkcamlp4" to make camlp4 executables linked with C code
* Added "pr_extend.cmo" to reconstitute EXTEND instructions

Camlp4 Version 0.6:
-------------------

--- Installing

* To compile camlp4, it is no more necessary to have the sources of the
  Objective Caml compiler available. It can be compiled like any other
  Objective Caml program.

--- Options of "camlp4"

* Added option -where: "camlp4 -where" prints the name of the standard
  library directory of Camlp4 and exit. So, the ocaml toplevel and the
  compiler can use the option:
	-I `camlp4 -where`

* Added option -nolib to not search for objects files in the installed
  library directory of Camlp4.

--- Interface of grammar library modules

* The function Grammar.keywords returns now a list of pairs. The pair is
  composed of a keyword and the number of times it is used in entries.

* Changed interface of Token and Grammar for lexers, so user lexers have
  to be changed.

--- New features in grammars

* New instruction "DELETE_RULE" provided by pa_extend.cmo to delete rules.
  Ex:
     DELETE_RULE Pcaml.expr: "if" END;
  deletes the "if" instruction of the language.

* Added the ability to parse some specific integer in grammars: a possible
  parameter to INT, like the ones for LIDENT and UIDENT.

* In instruction EXTEND, ability to omit "-> action", default is "-> ()"

* Ability to add antiquotation (between $'s) as symbol rule, of type string,
  interpreted as a keyword, in instruction EXTEND.

* Ability to put entries with qualified names (Foo.bar) in instruction EXTEND.

--- Quotations

* The module Ast has been renamed MLast. The quotation expander "q_ast.cmo"
  has been renamed "q_MLast.cmo".

* Quotation expanders are now of two kinds:
  - The "classical" type for expanders returning a string. These expanders
    have now a supplementary parameter: a boolean value set to "True"
    when the quotation is in a context of an expression an to "False"
    when the quotation is in a context of a pattern. These expanders,
    returning strings which are parsed afterwards, may work for some
    language syntax and/or language extensions used (e.g. may work for
    Righteous syntax and not for Ocaml syntax).
  - A new type of expander returning directly syntax trees. A pair
    of functions, for expressions and for patterns must be provided.
    These expanders are independant from the language syntax and/or
    extensions used.

* The predefined quotation expanders "ctyp_", "patt_" and "expr_" has
  been deleted; one can use "ctyp", "patt", and "expr" in position of
  pattern or expression.

--- Ocaml and Righteous syntaxes

* Fixed bug: "open Foo.Bar" was converted (pr_dump.cmo) into "open Bar.Foo"

* Corrected behavior different from Ocaml's: "^" and "@" were at the same
  level than "=": now, like Ocaml, they have a separated right associative
  level.

--- Grammars behavior

* While extending entries: default position is now "extension of the
  first level", instead of "adding a new level at the end".

* Another Change: in each precedence level, terminals are inserted before
  other symbols (non terminals, lists, options, etc), LIDENT "foo" before
  LIDENT (alone) and UIDENT "foo" before UIDENT (alone). New rules not
  factorizable are now inserted before the other rules.

* Changed algorithm of entries parsing: each precedence level is tested
  against the stream *before* its next precedences levels (instead of
  *after*):
       EXTEND e: [[ LIDENT "a" -> "xxx" ] | [ i = LIDENT -> i ]]; END;
  Now, parsing the entry e with the string "a" returns "xxx" instead of "a"

* Less keywords in instruction EXTEND (LEFTA, LIDENT, etc), which can be
  used now as normal identifiers.

* When inserting a new rule, a warning appears if a rule with the
  same production already existed (it is deleted).

* Parse error messages (Gstream.Error) are formatted => spaces trigger
  Format.print_space and newlines trigger Format.force_newline.


Camlp4 Version 0.5:
-------------------

* Possible creation of native code library (make opt)

* Ocaml and Righteous Syntax more complete

* Added pa_ru.cmo for compiling sequences of type unit (Righteous)

* Quotations AST
  - No more quotation long_id
  - Antiquotations for identifiers more simple

* Lot of small changes


Camlp4 Version 0.4:
-------------------

* First distributed version