update some programs

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13403 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2013-03-18 14:09:24 +00:00
parent 0b2eaffff3
commit 9e5de6fb02
4 changed files with 1292 additions and 11 deletions

View File

@ -20,7 +20,7 @@ calendar-2.03.2
camlimages
camlimages-4.0.1
camlp5
camlp5-6.06
camlp5-6.08
camlzip
camlzip-1.04
camomile
@ -30,7 +30,6 @@ comparelib-109.09.00
configfile
config-file-1.1
coq
coq-8.3pl4
coq-8.4pl1
core
core-109.09.00

View File

@ -216,7 +216,7 @@ typeconv: ${TYPECONV}.tar.gz findlib
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${TYPECONV} core
rm -rf ${TYPECONV} typeconv
distclean::
rm -f ${TYPECONV}.tar.gz
all: typeconv
@ -238,7 +238,7 @@ variantslib: ${VARIANTSLIB}.tar.gz findlib typeconv
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${VARIANTSLIB} core
rm -rf ${VARIANTSLIB} variantslib
distclean::
rm -f ${VARIANTSLIB}.tar.gz
all: variantslib
@ -260,7 +260,7 @@ pipebang: ${PIPEBANG}.tar.gz findlib typeconv
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${PIPEBANG} core
rm -rf ${PIPEBANG} pipebang
distclean::
rm -f ${PIPEBANG}.tar.gz
all: pipebang
@ -282,7 +282,7 @@ paounit: ${PAOUNIT}.tar.gz findlib typeconv
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${PAOUNIT} core
rm -rf ${PAOUNIT} paounit
distclean::
rm -f ${PAOUNIT}.tar.gz
all: paounit
@ -304,7 +304,7 @@ comparelib: ${COMPARELIB}.tar.gz findlib typeconv
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${COMPARELIB} core
rm -rf ${COMPARELIB} comparelib
distclean::
rm -f ${COMPARELIB}.tar.gz
all: comparelib
@ -326,7 +326,7 @@ binprot: ${BINPROT}.tar.gz findlib typeconv ounit
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${BINPROT} core
rm -rf ${BINPROT} binprot
distclean::
rm -f ${BINPROT}.tar.gz
all: binprot
@ -348,7 +348,7 @@ fieldslib: ${FIELDSLIB}.tar.gz findlib typeconv
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${FIELDSLIB} core
rm -rf ${FIELDSLIB} fieldslib
distclean::
rm -f ${FIELDSLIB}.tar.gz
all: fieldslib
@ -370,7 +370,7 @@ sexplib: ${SEXPLIB}.tar.gz findlib typeconv
ocaml setup.ml -install )
echo ${VERSION} >$@
clean::
rm -rf ${SEXPLIB} core
rm -rf ${SEXPLIB} sexplib
distclean::
rm -f ${SEXPLIB}.tar.gz
all: sexplib
@ -1354,7 +1354,7 @@ distclean::
all: kaputt
# http://pauillac.inria.fr/~ddr/camlp5/
CAMLP5=camlp5-6.06
CAMLP5=camlp5-6.08
${CAMLP5}.tgz:
${WGET} http://pauillac.inria.fr/~ddr/camlp5/distrib/src/$@
camlp5: ${CAMLP5}.tgz

1127
testsuite/external/camlp5-6.08.patch vendored Normal file

File diff suppressed because it is too large Load Diff

View File

@ -271,3 +271,158 @@
val rev_map : ('a -> 'b) -> 'a list -> 'b list
(** [List.rev_map f l] gives the same result as
{!List.rev}[ (]{!List.map}[ f l)], but is tail-recursive and
--- obrowser-1.1.1.orig/rt/caml/printexc.ml 2011-04-20 18:26:44.000000000 +0200
+++ obrowser-1.1.1/rt/caml/printexc.ml 2013-03-17 17:47:35.000000000 +0100
@@ -1,6 +1,6 @@
(***********************************************************************)
(* *)
-(* Objective Caml *)
+(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
@@ -11,8 +11,6 @@
(* *)
(***********************************************************************)
-(* $Id: printexc.ml 10272 2010-04-19 12:25:46Z frisch $ *)
-
open Printf;;
let printers = ref []
@@ -56,9 +54,12 @@
sprintf locfmt file line char (char+5) "Pattern matching failed"
| Assert_failure(file, line, char) ->
sprintf locfmt file line char (char+6) "Assertion failed"
+ | Undefined_recursive_module(file, line, char) ->
+ sprintf locfmt file line char (char+6) "Undefined recursive module"
| _ ->
let x = Obj.repr x in
- let constructor = (Obj.magic(Obj.field (Obj.field x 0) 0) : string) in
+ let constructor =
+ (Obj.magic (Obj.field (Obj.field x 0) 0) : string) in
constructor ^ (fields x) in
conv !printers
@@ -78,6 +79,11 @@
eprintf "Uncaught exception: %s\n" (to_string x);
exit 2
+type raw_backtrace
+
+external get_raw_backtrace:
+ unit -> raw_backtrace = "caml_get_exception_raw_backtrace"
+
type loc_info =
| Known_location of bool (* is_raise *)
* string (* filename *)
@@ -86,8 +92,13 @@
* int (* end char *)
| Unknown_location of bool (*is_raise*)
-external get_exception_backtrace:
- unit -> loc_info array option = "caml_get_exception_backtrace"
+(* to avoid warning *)
+let _ = [Known_location (false, "", 0, 0, 0); Unknown_location false]
+
+type backtrace = loc_info array
+
+external convert_raw_backtrace:
+ raw_backtrace -> backtrace option = "caml_convert_raw_backtrace"
let format_loc_info pos li =
let is_raise =
@@ -108,8 +119,8 @@
sprintf "%s unknown location"
info
-let print_backtrace outchan =
- match get_exception_backtrace() with
+let print_exception_backtrace outchan backtrace =
+ match backtrace with
| None ->
fprintf outchan
"(Program not linked with -g, cannot print stack backtrace)\n"
@@ -119,8 +130,15 @@
fprintf outchan "%s\n" (format_loc_info i a.(i))
done
-let get_backtrace () =
- match get_exception_backtrace() with
+let print_raw_backtrace outchan raw_backtrace =
+ print_exception_backtrace outchan (convert_raw_backtrace raw_backtrace)
+
+(* confusingly named: prints the global current backtrace *)
+let print_backtrace outchan =
+ print_raw_backtrace outchan (get_raw_backtrace ())
+
+let backtrace_to_string backtrace =
+ match backtrace with
| None ->
"(Program not linked with -g, cannot print stack backtrace)\n"
| Some a ->
@@ -131,6 +149,17 @@
done;
Buffer.contents b
+let raw_backtrace_to_string raw_backtrace =
+ backtrace_to_string (convert_raw_backtrace raw_backtrace)
+
+(* confusingly named:
+ returns the *string* corresponding to the global current backtrace *)
+let get_backtrace () =
+ (* we could use the caml_get_exception_backtrace primitive here, but
+ we hope to deprecate it so it's better to just compose the
+ raw stuff *)
+ backtrace_to_string (convert_raw_backtrace (get_raw_backtrace ()))
+
external record_backtrace: bool -> unit = "caml_record_backtrace"
external backtrace_status: unit -> bool = "caml_backtrace_status"
--- obrowser-1.1.1.orig/rt/caml/printexc.mli 2011-04-20 18:26:44.000000000 +0200
+++ obrowser-1.1.1/rt/caml/printexc.mli 2013-03-17 17:47:39.000000000 +0100
@@ -1,6 +1,6 @@
(***********************************************************************)
(* *)
-(* Objective Caml *)
+(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
@@ -11,8 +11,6 @@
(* *)
(***********************************************************************)
-(* $Id: printexc.mli 10457 2010-05-21 18:30:12Z doligez $ *)
-
(** Facilities for printing exceptions. *)
val to_string: exn -> string
@@ -77,5 +75,27 @@
in the reverse order of their registrations, until a printer returns
a [Some s] value (if no such printer exists, the runtime will use a
generic printer).
+
+ When using this mechanism, one should be aware that an exception backtrace
+ is attached to the thread that saw it raised, rather than to the exception
+ itself. Practically, it means that the code related to [fn] should not use
+ the backtrace if it has itself raised an exception before.
@since 3.11.2
*)
+
+(** {6 Raw backtraces} *)
+
+type raw_backtrace
+
+(** The abstract type [backtrace] stores exception backtraces in
+ a low-level format, instead of directly exposing them as string as
+ the [get_backtrace()] function does.
+
+ This allows to pay the performance overhead of representation
+ conversion and formatting only at printing time, which is useful
+ if you want to record more backtrace than you actually print.
+*)
+
+val get_raw_backtrace: unit -> raw_backtrace
+val print_raw_backtrace: out_channel -> raw_backtrace -> unit
+val raw_backtrace_to_string: raw_backtrace -> string