summaryrefslogtreecommitdiffstats
path: root/utils
diff options
context:
space:
mode:
authorMark Shinwell <mshinwell@janestreet.com>2014-05-01 12:50:20 +0000
committerMark Shinwell <mshinwell@janestreet.com>2014-05-01 12:50:20 +0000
commit521ac0213a11a22ca9e7dd588d7274072eb8e094 (patch)
tree35299f8e4bcf2045da96592b915c57d2d0637a08 /utils
parentf8df3c9aed4fe8b20762e1300188c6448c54e472 (diff)
weak dependencies with -trans-mod (github/ocamllabs/weak-depends 45e980a,21856a7,merge)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14719 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'utils')
-rw-r--r--utils/config.mlp14
-rw-r--r--utils/consistbl.ml15
-rw-r--r--utils/consistbl.mli7
3 files changed, 24 insertions, 12 deletions
diff --git a/utils/config.mlp b/utils/config.mlp
index e4c0d322a..db6fd20ed 100644
--- a/utils/config.mlp
+++ b/utils/config.mlp
@@ -49,15 +49,15 @@ let mkexe = "%%MKEXE%%"
let mkmaindll = "%%MKMAINDLL%%"
let exec_magic_number = "Caml1999X011"
-and cmi_magic_number = "Caml1999I016"
-and cmo_magic_number = "Caml1999O009"
-and cma_magic_number = "Caml1999A010"
-and cmx_magic_number = "Caml1999Y013"
-and cmxa_magic_number = "Caml1999Z012"
+and cmi_magic_number = "Caml1999I017"
+and cmo_magic_number = "Caml1999O010"
+and cma_magic_number = "Caml1999A011"
+and cmx_magic_number = "Caml1999Y014"
+and cmxa_magic_number = "Caml1999Z013"
and ast_impl_magic_number = "Caml1999M016"
and ast_intf_magic_number = "Caml1999N015"
-and cmxs_magic_number = "Caml2007D001"
-and cmt_magic_number = "Caml2012T003"
+and cmxs_magic_number = "Caml2007D002"
+and cmt_magic_number = "Caml2012T004"
let load_path = ref ([] : string list)
diff --git a/utils/consistbl.ml b/utils/consistbl.ml
index 4bc42dc5b..6adaf4112 100644
--- a/utils/consistbl.ml
+++ b/utils/consistbl.ml
@@ -40,8 +40,19 @@ let set tbl name crc source = Hashtbl.add tbl name (crc, source)
let source tbl name = snd (Hashtbl.find tbl name)
-let extract tbl =
- Hashtbl.fold (fun name (crc, auth) accu -> (name, crc) :: accu) tbl []
+let extract l tbl =
+ List.fold_left
+ (fun assc name ->
+ try
+ ignore (List.assoc name assc);
+ assc
+ with Not_found ->
+ try
+ let (crc, _) = Hashtbl.find tbl name in
+ (name, Some crc) :: assc
+ with Not_found ->
+ (name, None) :: assc)
+ [] l
let filter p tbl =
let to_remove = ref [] in
diff --git a/utils/consistbl.mli b/utils/consistbl.mli
index d3f2afcec..012bd734f 100644
--- a/utils/consistbl.mli
+++ b/utils/consistbl.mli
@@ -40,9 +40,10 @@ val source: t -> string -> string
if the latter has an associated CRC in [tbl].
Raise [Not_found] otherwise. *)
-val extract: t -> (string * Digest.t) list
- (* Return all bindings ([name], [crc]) contained in the given
- table. *)
+val extract: string list -> t -> (string * Digest.t option) list
+ (* [extract tbl names] returns an associative list mapping each string
+ in [names] to the CRC associated with it in [tbl]. If no CRC is
+ associated with a name then it is mapped to [None]. *)
val filter: (string -> bool) -> t -> unit
(* [filter pred tbl] removes from [tbl] table all (name, CRC) pairs