Skip to content

Commit 1f0b887

Browse files
author
Damien Doligez
committed
revert to the released version
git-svn-id: http://caml.inria.fr/svn/ocaml/release/4.01.0@14619 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
1 parent 35b0081 commit 1f0b887

File tree

16 files changed

+130
-291
lines changed

16 files changed

+130
-291
lines changed

Changes

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -94,10 +94,6 @@ Internals:
9494
Bug fixes:
9595
- PR#3236: Document the fact that queues are not thread-safe
9696
(Damien Doligez)
97-
- PR#6175: Fix open!
98-
- PR#5820: Fix camlp4 lexer roll back problem
99-
- PR#4855: 'camlp4 -I +dir' accepted, dir is related to 'camlp4 -where'
100-
- PR#6062: Fix a regression bug caused by commit 13047
10197
- PR#3468: (part 1) Sys_error documentation
10298
(Damien Doligez)
10399
- PR#3679: Warning display problems
@@ -374,8 +370,7 @@ Bug fixes:
374370
(Jacques Garrigue, report by Leo P. White)
375371
- PR#6164: segmentation fault on Num.power_num of 0/1
376372
(Fabrice Le Fessant, report by Johannes Kanig)
377-
- PR#6210: Camlp4 location error
378-
(Hongbo Zhang, report by Jun Furuse)
373+
379374
Feature wishes:
380375
- PR#5181: Merge common floating point constants in ocamlopt
381376
(Benedikt Meurer)
@@ -568,7 +563,6 @@ Installation procedure:
568563
(-runtime-variant) to select the debug runtime.
569564

570565
Bug Fixes:
571-
572566
- PR#1643: functions of the Lazy module whose named started with 'lazy_' have
573567
been deprecated, and new ones without the prefix added
574568
- PR#3571: in Bigarrays, call msync() before unmapping to commit changes

build/camlp4-bootstrap.sh

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,9 +34,9 @@ for target in $TARGETS camlp4/boot/Camlp4Ast.ml; do
3434
done
3535

3636
if [ -x ./boot/myocamlbuild.native ]; then
37-
OCAMLBUILD=./boot/myocamlbuild.native -no-ocamlfind
37+
OCAMLBUILD=./boot/myocamlbuild.native
3838
else
39-
OCAMLBUILD="./boot/ocamlrun boot/myocamlbuild -no-ocamlfind"
39+
OCAMLBUILD="./boot/ocamlrun boot/myocamlbuild"
4040
fi
4141
$OCAMLBUILD $TMPTARGETS $TARGETS
4242

camlp4/Camlp4/Camlp4Ast.partial.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -200,7 +200,7 @@
200200
(* while e do { e } *)
201201
| ExWhi of loc and expr and expr
202202
(* let open i in e *)
203-
| ExOpI of loc and ident and override_flag and expr
203+
| ExOpI of loc and ident and expr
204204
(* fun (type t) -> e *)
205205
(* let f x (type t) y z = e *)
206206
| ExFUN of loc and string and expr
@@ -334,7 +334,7 @@
334334
(* module type s = mt *)
335335
| StMty of loc and string and module_type
336336
(* open i *)
337-
| StOpn of loc and override_flag and ident
337+
| StOpn of loc and ident
338338
(* type t *)
339339
| StTyp of loc and ctyp
340340
(* value (rec)? bi *)

camlp4/Camlp4/Printers/OCaml.ml

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -493,10 +493,9 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
493493
| _ ->
494494
pp f "@[<hv0>@[<2>let %a%a@]@ @[<hv2>in@ %a@]@]"
495495
o#rec_flag r o#binding bi o#reset_semi#expr e ]
496-
| Ast.ExOpI _loc i ov e ->
497-
(* | <:expr< let open $i$ in $e$ >> -> *)
498-
pp f "@[<2>let open%a %a@]@ @[<2>in@ %a@]"
499-
o#override_flag ov o#ident i o#reset_semi#expr e
496+
| <:expr< let open $i$ in $e$ >> ->
497+
pp f "@[<2>let open %a@]@ @[<2>in@ %a@]"
498+
o#ident i o#reset_semi#expr e
500499
| <:expr< match $e$ with [ $a$ ] >> ->
501500
pp f "@[<hv0>@[<hv0>@[<2>match %a@]@ with@]%a@]"
502501
o#expr e o#match_case a
@@ -595,7 +594,7 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
595594
<:expr< if $_$ then $_$ else $_$ >> |
596595
<:expr< let $rec:_$ $_$ in $_$ >> |
597596
<:expr< let module $_$ = $_$ in $_$ >> |
598-
(* <:expr< let open $_$ in $_$ >> *)Ast.ExOpI _ _ _ _ |
597+
<:expr< let open $_$ in $_$ >> |
599598
<:expr< assert $_$ >> | <:expr< assert False >> |
600599
<:expr< lazy $_$ >> | <:expr< new $_$ >> |
601600
<:expr< object ($_$) $_$ end >> ->
@@ -867,11 +866,8 @@ module Make (Syntax : Sig.Camlp4Syntax) = struct
867866
| <:str_item< module type $s$ = $mt$ >> ->
868867
pp f "@[<2>module type %a =@ %a%(%)@]"
869868
o#var s o#module_type mt semisep
870-
| Ast.StOpn _loc ov sl ->
871-
(* | <:str_item< open $sl$ >> -> *)
872-
pp f "@[<2>open%a@ %a%(%)@]"
873-
o#override_flag ov
874-
o#ident sl semisep
869+
| <:str_item< open $sl$ >> ->
870+
pp f "@[<2>open@ %a%(%)@]" o#ident sl semisep
875871
| <:str_item< type $t$ >> ->
876872
pp f "@[<hv0>@[<hv2>type %a@]%(%)@]" o#ctyp t semisep
877873
| <:str_item< value $rec:r$ $bi$ >> ->

camlp4/Camlp4/Sig.ml

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -109,9 +109,7 @@ module type Loc = sig
109109
(** [merge loc1 loc2] Return a location that starts at [loc1] and end at
110110
[loc2]. *)
111111
value merge : t -> t -> t;
112-
(** [smart_merge loc1 loc2] Try to return a location that covers both [loc1] and [loc2]*)
113-
114-
value smart_merge : t -> t -> t ;
112+
115113
(** The stop pos becomes equal to the start pos. *)
116114
value join : t -> t;
117115

camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -863,9 +863,8 @@ value varify_constructors var_names =
863863
| ExWhi loc e1 el ->
864864
let e2 = ExSeq loc el in
865865
mkexp loc (Pexp_while (expr e1) (expr e2))
866-
| ExOpI loc i ov e ->
867-
let fresh = override_flag loc ov in
868-
mkexp loc (Pexp_open fresh (long_uident i) (expr e))
866+
| <:expr@loc< let open $i$ in $e$ >> ->
867+
mkexp loc (Pexp_open Fresh (long_uident i) (expr e))
869868
| <:expr@loc< (module $me$ : $pt$) >> ->
870869
mkexp loc (Pexp_constraint (mkexp loc (Pexp_pack (module_expr me)),
871870
Some (mktyp loc (Ptyp_package (package_type pt))), None))
@@ -1075,9 +1074,8 @@ value varify_constructors var_names =
10751074
| StRecMod loc mb ->
10761075
[mkstr loc (Pstr_recmodule (module_str_binding mb [])) :: l]
10771076
| StMty loc n mt -> [mkstr loc (Pstr_modtype (with_loc n loc) (module_type mt)) :: l]
1078-
| StOpn loc ov id ->
1079-
let fresh = override_flag loc ov in
1080-
[mkstr loc (Pstr_open fresh (long_uident id)) :: l]
1077+
| StOpn loc id ->
1078+
[mkstr loc (Pstr_open Fresh (long_uident id)) :: l]
10811079
| StTyp loc tdl -> [mkstr loc (Pstr_type (mktype_decl tdl [])) :: l]
10821080
| StVal loc rf bi ->
10831081
[mkstr loc (Pstr_value (mkrf rf) (binding bi [])) :: l]

camlp4/Camlp4/Struct/Lexer.mll

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,7 @@ module Make (Token : Sig.Camlp4Token)
144144
let is_in_comment c = c.in_comment
145145
let in_comment c = { (c) with in_comment = true }
146146
let set_start_p c = c.lexbuf.lex_start_p <- Loc.start_pos c.loc
147-
let move_start_p shift c = (* FIXME Please see PR#5820*)
147+
let move_start_p shift c =
148148
let p = c.lexbuf.lex_start_p in
149149
c.lexbuf.lex_start_p <- { (p) with pos_cnum = p.pos_cnum + shift }
150150

@@ -308,8 +308,7 @@ module Make (Token : Sig.Camlp4Token)
308308
parse comment (in_comment c); COMMENT (buff_contents c) }
309309
| "*)"
310310
{ warn Comment_not_end (Loc.of_lexbuf lexbuf) ;
311-
c.lexbuf.lex_curr_pos <- c.lexbuf.lex_curr_pos - 1;
312-
SYMBOL "*" }
311+
move_start_p (-1) c; SYMBOL "*" }
313312
| "<<" (quotchar* as beginning)
314313
{ if quotations c
315314
then (move_start_p (-String.length beginning);

camlp4/Camlp4/Struct/Loc.ml

Lines changed: 0 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -98,33 +98,6 @@ value dump f x =
9898

9999
value start_pos = { line = 1 ; bol = 0 ; off = 0 };
100100

101-
value min_pos (x:pos) (y:pos) =
102-
if x.off < y.off
103-
then x
104-
else y;
105-
value max_pos (x:pos) (y:pos) =
106-
if x.off > y.off
107-
then x
108-
else y;
109-
110-
value smart_merge (a:t) (b:t) =
111-
if a == b then a
112-
else
113-
match (a,b) with
114-
[ ({ghost=False;start=a0;stop=a1;file_name = f},
115-
{ghost=False;start=b0;stop=b1;_}) ->
116-
{ghost = False;
117-
start = min_pos a0 b0;
118-
stop = max_pos a1 b1;
119-
file_name = f
120-
}
121-
| ({ghost = True;_},{ghost=True;_})
122-
| ({ghost = True;_},_) -> {(a) with stop = b.stop }
123-
| ({ghost = _;_},{ghost = True;_}) ->
124-
{(b) with start = a.start }
125-
]
126-
;
127-
128101
value ghost =
129102
{ file_name = "ghost-location";
130103
start = start_pos;

camlp4/Camlp4Bin.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -236,7 +236,7 @@ value input_file x =
236236
};
237237

238238
value initial_spec_list =
239-
[("-I", Arg.String (fun x -> input_file (IncludeDir (Camlp4_import.Misc.expand_directory Camlp4_config.camlp4_standard_library x))),
239+
[("-I", Arg.String (fun x -> input_file (IncludeDir x)),
240240
"<directory> Add directory in search patch for object files.");
241241
("-where", Arg.Unit print_stdlib,
242242
"Print camlp4 library directory and exit.");

camlp4/Camlp4Filters/Camlp4FoldGenerator.ml

Lines changed: 8 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -496,7 +496,7 @@ module Make (AstFilters : Camlp4.Sig.AstFilters) = struct
496496
StringMap.add name (name, <:ident< $lid:name$ >>, tl, tk, False) acc
497497
| _ -> assert False ];
498498

499-
value generate_class_implem ?(virtual_flag=False) mode c tydcl n =
499+
value generate_class_implem mode c tydcl n =
500500
let tyMap = tyMap_of_type_decls tydcl StringMap.empty in
501501
let module M = Gen(struct value size = n; value mode = mode; end) in
502502
let generated = M.generate_structure tyMap in
@@ -515,13 +515,11 @@ module Make (AstFilters : Camlp4.Sig.AstFilters) = struct
515515
<:ctyp< ! 'a . $M.method_type_of_type <:ctyp< 'a >> <:ctyp< 'a >> [] []$ >>
516516
in
517517
let unknown =
518-
<:class_str_item< method unknown : $gen_type$ = $M.default_expr$ >> in
519-
if not virtual_flag then
520-
<:str_item< class $lid:c$ = object (o : 'self_type) $generated$; $failure$; $unknown$ end >>
521-
else
522-
<:str_item< class virtual $lid:c$ = object (o : 'self_type) $generated$; $failure$; $unknown$ end >>;
518+
<:class_str_item< method unknown : $gen_type$ = $M.default_expr$ >>
519+
in
520+
<:str_item< class $lid:c$ = object (o : 'self_type) $generated$; $failure$; $unknown$ end >>;
523521

524-
value generate_class_interf ?(virtual_flag=False) mode c tydcl n =
522+
value generate_class_interf mode c tydcl n =
525523
let tyMap = tyMap_of_type_decls tydcl StringMap.empty in
526524
let module M = Gen(struct value size = n; value mode = mode; end) in
527525
let generated = M.generate_signature tyMap in
@@ -540,10 +538,7 @@ module Make (AstFilters : Camlp4.Sig.AstFilters) = struct
540538
let unknown =
541539
<:class_sig_item< method unknown : $gen_type$ >>
542540
in
543-
if not virtual_flag then
544-
<:sig_item< class $lid:c$ : object ('self_type) $generated$; $failure$; $unknown$ end >>
545-
else
546-
<:sig_item< class virtual $lid:c$ : object ('self_type) $generated$; $failure$; $unknown$ end >> ;
541+
<:sig_item< class $lid:c$ : object ('self_type) $generated$; $failure$; $unknown$ end >>;
547542

548543
value processor =
549544
let last = ref <:ctyp<>> in
@@ -570,19 +565,12 @@ module Make (AstFilters : Camlp4.Sig.AstFilters) = struct
570565
(* backward compatibility *)
571566
| <:str_item@_loc< class $lid:c$ = Camlp4Filters.GenerateFold.generated >> ->
572567
generate_class_implem Fold c last.val 1
573-
| <:str_item@_loc< class virtual $lid:c$ = Camlp4Filters.GenerateFold.generated >> ->
574-
generate_class_implem ~virtual_flag:True Fold c last.val 1
575-
576568
| <:str_item@_loc< class $lid:c$ = Camlp4Filters.GenerateMap.generated >> ->
577569
generate_class_implem Map c last.val 1
578-
| <:str_item@_loc< class virtual $lid:c$ = Camlp4Filters.GenerateMap.generated >> ->
579-
generate_class_implem ~virtual_flag:True Map c last.val 1
580570

581571
(* Handle Camlp4(Fold|Map|FoldMap)\d*Generator *)
582572
| <:str_item@_loc< class $lid:c$ = $uid:m$.generated >> ->
583-
generate_class_from_module_name (generate_class_implem ~virtual_flag:False) c st m
584-
| <:str_item@_loc< class virtual $lid:c$ = $uid:m$.generated >> ->
585-
generate_class_from_module_name (generate_class_implem ~virtual_flag:True) c st m
573+
generate_class_from_module_name generate_class_implem c st m
586574

587575
(* It's a hack to force to recurse on the left to right order *)
588576
| <:str_item< $st1$; $st2$ >> ->
@@ -598,19 +586,12 @@ module Make (AstFilters : Camlp4.Sig.AstFilters) = struct
598586
(* backward compatibility *)
599587
| <:sig_item@_loc< class $lid:c$ : Camlp4Filters.GenerateFold.generated >> ->
600588
generate_class_interf Fold c last.val 1
601-
| <:sig_item@_loc< class virtual $lid:c$ : Camlp4Filters.GenerateFold.generated >> ->
602-
generate_class_interf ~virtual_flag:True Fold c last.val 1
603-
604589
| <:sig_item@_loc< class $lid:c$ : Camlp4Filters.GenerateMap.generated >> ->
605590
generate_class_interf Map c last.val 1
606-
| <:sig_item@_loc< class virtual $lid:c$ : Camlp4Filters.GenerateMap.generated >> ->
607-
generate_class_interf ~virtual_flag:True Map c last.val 1
608591

609592
(* Handle Camlp4(Fold|Map|FoldMap)\d*Generator *)
610593
| <:sig_item@_loc< class $lid:c$ : $uid:m$.generated >> ->
611-
generate_class_from_module_name (generate_class_interf ~virtual_flag:False) c sg m
612-
| <:sig_item@_loc< class virtual $lid:c$ : $uid:m$.generated >> ->
613-
generate_class_from_module_name (generate_class_interf ~virtual_flag:True) c sg m
594+
generate_class_from_module_name generate_class_interf c sg m
614595

615596
(* It's a hack to force to recurse on the left to right order *)
616597
| <:sig_item< $sg1$; $sg2$ >> ->

0 commit comments

Comments
 (0)