Makefiles: fix disparition de weak.cmo

Changement de type des fonctions iter


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1747 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 1997-10-31 12:59:29 +00:00
parent 100004bca8
commit b8ccccff49
15 changed files with 36 additions and 36 deletions

View File

@ -2,8 +2,8 @@ genlex.cmi: stream.cmi
parsing.cmi: lexing.cmi obj.cmi
arg.cmo: array.cmi list.cmi printf.cmi string.cmi sys.cmi arg.cmi
arg.cmx: array.cmx list.cmx printf.cmx string.cmx sys.cmx arg.cmi
array.cmo: list.cmi array.cmi
array.cmx: list.cmx array.cmi
array.cmo: array.cmi list.cmi array.cmi
array.cmx: array.cmx list.cmx array.cmi
callback.cmo: obj.cmi callback.cmi
callback.cmx: obj.cmx callback.cmi
char.cmo: char.cmi
@ -30,8 +30,8 @@ map.cmo: map.cmi
map.cmx: map.cmi
marshal.cmo: string.cmi marshal.cmi
marshal.cmx: string.cmx marshal.cmi
obj.cmo: obj.cmi
obj.cmx: obj.cmi
obj.cmo: marshal.cmi obj.cmi
obj.cmx: marshal.cmx obj.cmi
oo.cmo: array.cmi hashtbl.cmi list.cmi map.cmi obj.cmi random.cmi sort.cmi \
sys.cmi oo.cmi
oo.cmx: array.cmx hashtbl.cmx list.cmx map.cmx obj.cmx random.cmx sort.cmx \
@ -56,8 +56,8 @@ stack.cmo: list.cmi stack.cmi
stack.cmx: list.cmx stack.cmi
stream.cmo: list.cmi obj.cmi string.cmi stream.cmi
stream.cmx: list.cmx obj.cmx string.cmx stream.cmi
string.cmo: char.cmi list.cmi string.cmi
string.cmx: char.cmx list.cmx string.cmi
string.cmo: char.cmi list.cmi string.cmi string.cmi
string.cmx: char.cmx list.cmx string.cmx string.cmi
sys.cmo: sys.cmi
sys.cmx: sys.cmi
weak.cmo: obj.cmi weak.cmi

View File

@ -14,7 +14,7 @@ OBJS=pervasives.cmo list.cmo char.cmo string.cmo array.cmo sys.cmo \
lexing.cmo parsing.cmo \
set.cmo map.cmo stack.cmo queue.cmo stream.cmo \
printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo \
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo marshal.cmo \
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo \
lazy.cmo
all: stdlib.cma std_exit.cmo camlheader

View File

@ -8,7 +8,8 @@ OBJS = pervasives.cmo list.cmo char.cmo string.cmo array.cmo sys.cmo
lexing.cmo parsing.cmo ¶
set.cmo map.cmo stack.cmo queue.cmo stream.cmo ¶
printf.cmo format.cmo arg.cmo printexc.cmo gc.cmo ¶
digest.cmo random.cmo oo.cmo genlex.cmo weak.cmo lazy.cmo
digest.cmo random.cmo oo.cmo genlex.cmo callback.cmo weak.cmo ¶
lazy.cmo
all Ä stdlib.cma std_exit.cmo camlheader

View File

@ -79,9 +79,9 @@ val to_list: 'a array -> 'a list
val of_list: 'a list -> 'a array
(* [Array.of_list l] returns a fresh array containing the elements
of [l]. *)
val iter: ('a -> 'b) -> 'a array -> unit
val iter: ('a -> unit) -> 'a array -> unit
(* [Array.iter f a] applies function [f] in turn to all
the elements of [a], discarding all the results:
the elements of [a]. It is equivalent to
[f a.(0); f a.(1); ...; f a.(Array.length a - 1); ()]. *)
val map: ('a -> 'b) -> 'a array -> 'b array
(* [Array.map f a] applies function [f] to all the elements of [a],

View File

@ -134,7 +134,7 @@ module type S =
val remove: 'a t -> key -> unit
val find: 'a t -> key -> 'a
val find_all: 'a t -> key -> 'a list
val iter: (key -> 'a -> 'b) -> 'a t -> unit
val iter: (key -> 'a -> unit) -> 'a t -> unit
end
module Make(H: HashedType): (S with type key = H.t) =

View File

@ -52,9 +52,8 @@ val remove : ('a, 'b) t -> 'a -> unit
restoring the previous binding if it exists.
It does nothing if [x] is not bound in [tbl]. *)
val iter : ('a -> 'b -> 'c) -> ('a, 'b) t -> unit
(* [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl],
discarding all the results.
val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit
(* [Hashtbl.iter f tbl] applies [f] to all bindings in table [tbl].
[f] receives the key as first argument, and the associated value
as second argument. The order in which the bindings are passed to
[f] is unspecified. Each binding is presented exactly once
@ -91,7 +90,7 @@ module type S =
val remove: 'a t -> key -> unit
val find: 'a t -> key -> 'a
val find_all: 'a t -> key -> 'a list
val iter: (key -> 'a -> 'b) -> 'a t -> unit
val iter: (key -> 'a -> unit) -> 'a t -> unit
end
module Make(H: HashedType): (S with type key = H.t)

View File

@ -52,7 +52,8 @@ let rec map f = function
| a::l -> let r = f a in r :: map f l
let rec iter f = function
[] -> ()
| [] -> ()
| [a] -> f a
| a::l -> f a; iter f l
let rec fold_left f accu l =

View File

@ -33,9 +33,9 @@ val flatten : 'a list list -> 'a list
(** Iterators *)
val iter : ('a -> 'b) -> 'a list -> unit
val iter : ('a -> unit) -> 'a list -> unit
(* [List.iter f [a1; ...; an]] applies function [f] in turn to
[a1; ...; an], discarding all the results. It is equivalent to
[a1; ...; an]. It is equivalent to
[begin f a1; f a2; ...; f an; () end]. *)
val map : ('a -> 'b) -> 'a list -> 'b list
(* [List.map f [a1; ...; an]] applies function [f] to [a1, ..., an],
@ -50,9 +50,9 @@ val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b
(** Iterators on two lists *)
val iter2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> unit
val iter2 : ('a -> 'b -> unit) -> 'a list -> 'b list -> unit
(* [List.iter2 f [a1; ...; an] [b1; ...; bn]] calls in turn
[f a1 b1; ...; f an bn], discarding the results.
[f a1 b1; ...; f an bn].
Raise [Invalid_argument] if the two lists have
different lengths. *)
val map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list

View File

@ -25,7 +25,7 @@ module type S =
val add: key -> 'a -> 'a t -> 'a t
val find: key -> 'a t -> 'a
val remove: key -> 'a t -> 'a t
val iter: (key -> 'a -> 'b) -> 'a t -> unit
val iter: (key -> 'a -> unit) -> 'a t -> unit
val map: ('a -> 'b) -> 'a t -> 'b t
val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b
end

View File

@ -54,9 +54,8 @@ module type S =
val remove: key -> 'a t -> 'a t
(* [remove x m] returns a map containing the same bindings as
[m], except for [x] which is unbound in the returned map. *)
val iter: (key -> 'a -> 'b) -> 'a t -> unit
(* [iter f m] applies [f] to all bindings in map [m],
discarding the results.
val iter: (key -> 'a -> unit) -> 'a t -> unit
(* [iter f m] applies [f] to all bindings in map [m].
[f] receives the key as first argument, and the associated value
as second argument. The order in which the bindings are passed to
[f] is unspecified. Only current bindings are presented to [f]:
@ -72,7 +71,7 @@ module type S =
where [k1 ... kN] are the keys of all bindings in [m],
and [d1 ... dN] are the associated data.
The order in which the bindings are presented to [f] is
not specified. *)
unspecified. *)
end
module Make(Ord: OrderedType): (S with type key = Ord.t)

View File

@ -35,7 +35,7 @@ val clear : 'a t -> unit
(* Discard all elements from a queue. *)
val length: 'a t -> int
(* Return the number of elements in a queue. *)
val iter: ('a -> 'b) -> 'a t -> unit
val iter: ('a -> unit) -> 'a t -> unit
(* [iter f q] applies [f] in turn to all elements of [q],
from the least recently entered to the most recently entered.
The queue itself is unchanged. *)

View File

@ -34,7 +34,7 @@ module type S =
val compare: t -> t -> int
val equal: t -> t -> bool
val subset: t -> t -> bool
val iter: (elt -> 'a) -> t -> unit
val iter: (elt -> unit) -> t -> unit
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
val cardinal: t -> int
val elements: t -> elt list

View File

@ -67,23 +67,23 @@ module type S =
val subset: t -> t -> bool
(* [subset s1 s2] tests whether the set [s1] is a subset of
the set [s2]. *)
val iter: (elt -> 'a) -> t -> unit
(* [iter f s] applies [f] in turn to all elements of [s], and
discards the results. The elements of [s] are presented to [f]
in a non-specified order. *)
val iter: (elt -> unit) -> t -> unit
(* [iter f s] applies [f] in turn to all elements of [s].
The order in which the elements of [s] are presented to [f]
is unspecified. *)
val fold: (elt -> 'a -> 'a) -> t -> 'a -> 'a
(* [fold f s a] computes [(f xN ... (f x2 (f x1 a))...)],
where [x1 ... xN] are the elements of [s].
The order in which elements of [s] are presented to [f] is
not specified. *)
unspecified. *)
val cardinal: t -> int
(* Return the number of elements of a set. *)
val elements: t -> elt list
(* Return the list of all elements of the given set.
The elements appear in the list in some non-specified order. *)
The elements appear in the list in some unspecified order. *)
val choose: t -> elt
(* Return one element of the given set, or raise [Not_found] if
the set is empty. Which element is chosen is not specified,
the set is empty. Which element is chosen is unspecified,
but equal elements will be chosen for equal sets. *)
end

View File

@ -32,7 +32,7 @@ val clear : 'a t -> unit
(* Discard all elements from a stack. *)
val length: 'a t -> int
(* Return the number of elements in a stack. *)
val iter: ('a -> 'b) -> 'a t -> unit
val iter: ('a -> unit) -> 'a t -> unit
(* [iter f s] applies [f] in turn to all elements of [s],
from the element at the top of the stack to the element at the
bottom of the stack. The stack itself is unchanged. *)

View File

@ -44,7 +44,7 @@ val of_channel : in_channel -> char t;;
(** Stream iterator *)
val iter : ('a -> 'b) -> 'a t -> unit;;
val iter : ('a -> unit) -> 'a t -> unit;;
(* [Stream.iter f s] scans the whole stream s, applying function [f]
in turn to each stream element encountered. *)