MoreLabels for better 3.02 compatibility

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3846 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2001-10-03 12:21:22 +00:00
parent d08af5d632
commit e66c96ac34
5 changed files with 141 additions and 2 deletions

View File

@ -1,5 +1,6 @@
format.cmi: buffer.cmi
genlex.cmi: stream.cmi
moreLabels.cmi: hashtbl.cmi
parsing.cmi: lexing.cmi obj.cmi
printf.cmi: buffer.cmi
arg.cmo: array.cmi list.cmi printf.cmi string.cmi sys.cmi arg.cmi
@ -42,6 +43,8 @@ map.cmo: map.cmi
map.cmx: map.cmi
marshal.cmo: string.cmi marshal.cmi
marshal.cmx: string.cmx marshal.cmi
moreLabels.cmo: hashtbl.cmi map.cmi set.cmi moreLabels.cmi
moreLabels.cmx: hashtbl.cmx map.cmx set.cmx moreLabels.cmi
nativeint.cmo: sys.cmi nativeint.cmi
nativeint.cmx: sys.cmx nativeint.cmi
obj.cmo: marshal.cmi obj.cmi

View File

@ -30,7 +30,7 @@ BASIC=pervasives.cmo array.cmo list.cmo char.cmo string.cmo sys.cmo \
buffer.cmo printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo \
lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo
LABELLED=arrayLabels.ml listLabels.ml stringLabels.ml
LABELLED=arrayLabels.ml listLabels.ml stringLabels.ml moreLabels.ml
OBJS=$(BASIC) labelled.cmo stdLabels.cmo
ALLOBJS=$(BASIC) $(LABELLED:.ml=.cmo) stdLabels.cmo

View File

@ -28,7 +28,7 @@ BASIC=pervasives.cmo array.cmo list.cmo char.cmo string.cmo sys.cmo \
buffer.cmo printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo \
lazy.cmo filename.cmo int32.cmo int64.cmo nativeint.cmo
LABELLED=arrayLabels.ml listLabels.ml stringLabels.ml
LABELLED=arrayLabels.ml listLabels.ml stringLabels.ml moreLabels.ml
OBJS=$(BASIC) labelled.cmo stdLabels.cmo
ALLOBJS=$(BASIC) $(LABELLED:.ml=.cmo) stdLabels.cmo

21
stdlib/moreLabels.ml Normal file
View File

@ -0,0 +1,21 @@
(***********************************************************************)
(* *)
(* Objective Caml *)
(* *)
(* Jacques Garrigue, Kyoto University RIMS *)
(* *)
(* Copyright 2001 Institut National de Recherche en Informatique et *)
(* en Automatique. All rights reserved. This file is distributed *)
(* under the terms of the GNU Library General Public License. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* Module [MoreLabels]: meta-module for compatibility labelled libraries *)
module Hashtbl = Hashtbl
module Map = Map
module Set = Set

115
stdlib/moreLabels.mli Normal file
View File

@ -0,0 +1,115 @@
(***********************************************************************)
(* *)
(* Objective Caml *)
(* *)
(* Jacques Garrigue, Kyoto University RIMS *)
(* *)
(* Copyright 2001 Institut National de Recherche en Informatique et *)
(* en Automatique. All rights reserved. This file is distributed *)
(* under the terms of the GNU Library General Public License. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* Module [StdLabels]: standard labeled libraries *)
(* This meta-module provides labelized version of the [Hashtbl],
[Map] and [Set] modules.
They only differ by their labels. They are provided for backwards
compatibility with previous versions of Objective Caml, and it is
preferable to avoid them in new projects.
*)
module Hashtbl : sig
type ('a, 'b) t = ('a, 'b) Hashtbl.t
val create : int -> ('a, 'b) t
val clear : ('a, 'b) t -> unit
val add : ('a, 'b) t -> key:'a -> data:'b -> unit
val find : ('a, 'b) t -> 'a -> 'b
val find_all : ('a, 'b) t -> 'a -> 'b list
val mem : ('a, 'b) t -> 'a -> bool
val remove : ('a, 'b) t -> 'a -> unit
val replace : ('a, 'b) t -> key:'a -> data:'b -> unit
val iter : f:(key:'a -> data:'b -> unit) -> ('a, 'b) t -> unit
val fold :
f:(key:'a -> data:'b -> 'c -> 'c) ->
('a, 'b) t -> init:'c -> 'c
module type HashedType = Hashtbl.HashedType
module type S =
sig
type key
and 'a t
val create : int -> 'a t
val clear : 'a t -> unit
val add : 'a t -> key:key -> data:'a -> unit
val remove : 'a t -> key -> unit
val find : 'a t -> key -> 'a
val find_all : 'a t -> key -> 'a list
val replace : 'a t -> key:key -> data:'a -> unit
val mem : 'a t -> key -> bool
val iter : f:(key:key -> data:'a -> unit) -> 'a t -> unit
val fold :
f:(key:key -> data:'a -> 'b -> 'b) ->
'a t -> init:'b -> 'b
end
module Make : functor (H : HashedType) -> S with type key = H.t
val hash : 'a -> int
external hash_param : int -> int -> 'a -> int
= "hash_univ_param" "noalloc"
end
module Map : sig
module type OrderedType = Map.OrderedType
module type S =
sig
type key
and (+'a) t
val empty : 'a t
val add : key:key -> data:'a -> 'a t -> 'a t
val find : key -> 'a t -> 'a
val remove : key -> 'a t -> 'a t
val mem : key -> 'a t -> bool
val iter : f:(key:key -> data:'a -> unit) -> 'a t -> unit
val map : f:('a -> 'b) -> 'a t -> 'b t
val mapi : f:(key -> 'a -> 'b) -> 'a t -> 'b t
val fold :
f:(key:key -> data:'a -> 'b -> 'b) ->
'a t -> init:'b -> 'b
end
module Make : functor (Ord : OrderedType) -> S with type key = Ord.t
end
module Set : sig
module type OrderedType = Set.OrderedType
module type S =
sig
type elt
and t
val empty : t
val is_empty : t -> bool
val mem : elt -> t -> bool
val add : elt -> t -> t
val singleton : elt -> t
val remove : elt -> t -> t
val union : t -> t -> t
val inter : t -> t -> t
val diff : t -> t -> t
val compare : t -> t -> int
val equal : t -> t -> bool
val subset : t -> t -> bool
val iter : f:(elt -> unit) -> t -> unit
val fold : f:(elt -> 'a -> 'a) -> t -> init:'a -> 'a
val for_all : f:(elt -> bool) -> t -> bool
val exists : f:(elt -> bool) -> t -> bool
val filter : f:(elt -> bool) -> t -> t
val partition : f:(elt -> bool) -> t -> t * t
val cardinal : t -> int
val elements : t -> elt list
val min_elt : t -> elt
val max_elt : t -> elt
val choose : t -> elt
end
module Make : functor (Ord : OrderedType) -> S with type elt = Ord.t
end