diff options
Diffstat (limited to 'stdlib')
-rw-r--r-- | stdlib/.depend | 4 | ||||
-rw-r--r-- | stdlib/Makefile | 31 | ||||
-rw-r--r-- | stdlib/arg.mli | 5 | ||||
-rw-r--r-- | stdlib/array.mli | 28 | ||||
-rw-r--r-- | stdlib/buffer.mli | 6 | ||||
-rw-r--r-- | stdlib/digest.mli | 6 | ||||
-rw-r--r-- | stdlib/filename.mli | 6 | ||||
-rw-r--r-- | stdlib/format.mli | 12 | ||||
-rw-r--r-- | stdlib/hashtbl.mli | 24 | ||||
-rw-r--r-- | stdlib/lexing.mli | 4 | ||||
-rw-r--r-- | stdlib/list.mli | 56 | ||||
-rw-r--r-- | stdlib/map.mli | 14 | ||||
-rw-r--r-- | stdlib/marshal.mli | 13 | ||||
-rw-r--r-- | stdlib/obj.mli | 8 | ||||
-rw-r--r-- | stdlib/oo.mli | 2 | ||||
-rw-r--r-- | stdlib/pervasives.ml | 2 | ||||
-rw-r--r-- | stdlib/pervasives.mli | 26 | ||||
-rw-r--r-- | stdlib/queue.mli | 2 | ||||
-rw-r--r-- | stdlib/set.mli | 10 | ||||
-rw-r--r-- | stdlib/sort.mli | 6 | ||||
-rw-r--r-- | stdlib/stack.mli | 2 | ||||
-rw-r--r-- | stdlib/stream.mli | 2 | ||||
-rw-r--r-- | stdlib/string.mli | 35 | ||||
-rw-r--r-- | stdlib/sys.mli | 2 | ||||
-rw-r--r-- | stdlib/weak.mli | 12 |
25 files changed, 180 insertions, 138 deletions
diff --git a/stdlib/.depend b/stdlib/.depend index 766b0d23e..8a555275f 100644 --- a/stdlib/.depend +++ b/stdlib/.depend @@ -34,6 +34,8 @@ map.cmo: map.cmi map.cmx: map.cmi marshal.cmo: string.cmi marshal.cmi marshal.cmx: string.cmx marshal.cmi +morelabel.cmo: buffer.cmi hashtbl.cmi map.cmi set.cmi morelabel.cmi +morelabel.cmx: buffer.cmx hashtbl.cmx map.cmx set.cmx morelabel.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 \ @@ -58,6 +60,8 @@ sort.cmo: array.cmi sort.cmi sort.cmx: array.cmx sort.cmi stack.cmo: list.cmi stack.cmi stack.cmx: list.cmx stack.cmi +stdlabel.cmo: array.cmi list.cmi string.cmi stdlabel.cmi +stdlabel.cmx: array.cmx list.cmx string.cmx stdlabel.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 diff --git a/stdlib/Makefile b/stdlib/Makefile index ab86ed0e8..84f0cd0ce 100644 --- a/stdlib/Makefile +++ b/stdlib/Makefile @@ -102,6 +102,37 @@ pervasives.p.cmx: pervasives.ml oo.cmi: oo.mli $(CAMLC) $(COMPFLAGS) -nopervasives -c oo.mli +# stdlabel.cmo and morelabel.cmo use -labelize +stdlabel.cmo: stdlabel.ml + $(CAMLC) $(COMPFLAGS) -labelize -c stdlabel.ml + +stdlabel.cmx: stdlabel.ml + $(CAMLOPT) $(OPTCOMPFLAGS) -labelize -c stdlabel.ml + +stdlabel.p.cmx: stdlabel.ml + @if test -f stdlabel.cmx; then mv stdlabel.cmx stdlabel.n.cmx; else :; fi + @if test -f stdlabel.o; then mv stdlabel.o stdlabel.n.o; else :; fi + $(CAMLOPT) $(OPTCOMPFLAGS) -p -labelize -c stdlabel.ml + mv stdlabel.cmx stdlabel.p.cmx + mv stdlabel.o stdlabel.p.o + @if test -f stdlabel.n.cmx; then mv stdlabel.n.cmx stdlabel.cmx; else :; fi + @if test -f stdlabel.n.o; then mv stdlabel.n.o stdlabel.o; else :; fi + +morelabel.cmo: morelabel.ml + $(CAMLC) $(COMPFLAGS) -labelize -c morelabel.ml + +morelabel.cmx: morelabel.ml + $(CAMLOPT) $(OPTCOMPFLAGS) -labelize -c morelabel.ml + +morelabel.p.cmx: morelabel.ml + @if test -f morelabel.cmx; then mv morelabel.cmx morelabel.n.cmx; else :; fi + @if test -f morelabel.o; then mv morelabel.o morelabel.n.o; else :; fi + $(CAMLOPT) $(OPTCOMPFLAGS) -p -labelize -c morelabel.ml + mv morelabel.cmx morelabel.p.cmx + mv morelabel.o morelabel.p.o + @if test -f morelabel.n.cmx; then mv morelabel.n.cmx morelabel.cmx; else :; fi + @if test -f morelabel.n.o; then mv morelabel.n.o morelabel.o; else :; fi + .SUFFIXES: .mli .ml .cmi .cmo .cmx .p.cmx .mli.cmi: diff --git a/stdlib/arg.mli b/stdlib/arg.mli index f50647e39..7f9739d3b 100644 --- a/stdlib/arg.mli +++ b/stdlib/arg.mli @@ -51,7 +51,8 @@ type spec = (* The concrete type describing the behavior associated with a keyword. *) -val parse : (string * spec * string) list -> (string -> unit) -> string -> unit +val parse : keywords:(string * spec * string) list -> + others:(string -> unit) -> errmsg:string -> unit (* [Arg.parse speclist anonfun usage_msg] parses the command line. [speclist] is a list of triples [(key, spec, doc)]. @@ -84,7 +85,7 @@ exception Bad of string message to reject invalid arguments. *) -val usage: (string * spec * string) list -> string -> unit +val usage: keywords:(string * spec * string) list -> errmsg:string -> unit (* [Arg.usage speclist usage_msg] prints an error message including the list of valid options. This is the same message that diff --git a/stdlib/array.mli b/stdlib/array.mli index d889d3a8d..9beb68082 100644 --- a/stdlib/array.mli +++ b/stdlib/array.mli @@ -29,8 +29,8 @@ external set: 'a array -> int -> 'a -> unit = "%array_safe_set" Raise [Invalid_argument "Array.set"] if [n] is outside the range 0 to [Array.length a - 1]. You can also write [a.(n) <- x] instead of [Array.set a n x]. *) -external make: int -> 'a -> 'a array = "make_vect" -external create: int -> 'a -> 'a array = "make_vect" +external make: len:int -> 'a -> 'a array = "make_vect" +external create: len:int -> 'a -> 'a array = "make_vect" (* [Array.make n x] returns a fresh array of length [n], initialized with [x]. All the elements of this new array are initially @@ -42,13 +42,13 @@ external create: int -> 'a -> 'a array = "make_vect" If the value of [x] is a floating-point number, then the maximum size is only [Sys.max_array_length / 2]. [Array.create] is a deprecated alias for [Array.make]. *) -val init: int -> (int -> 'a) -> 'a array +val init: len:int -> fun:(int -> 'a) -> 'a array (* [Array.init n f] returns a fresh array of length [n], with element number [i] initialized to the result of [f i]. In other terms, [Array.init n f] tabulates the results of [f] applied to the integers [0] to [n-1]. *) -val make_matrix: int -> int -> 'a -> 'a array array -val create_matrix: int -> int -> 'a -> 'a array array +val make_matrix: dimx:int -> dimy:int -> 'a -> 'a array array +val create_matrix: dimx:int -> dimy:int -> 'a -> 'a array array (* [Array.make_matrix dimx dimy e] returns a two-dimensional array (an array of arrays) with first dimension [dimx] and second dimension [dimy]. All the elements of this new matrix @@ -66,7 +66,7 @@ val append: 'a array -> 'a array -> 'a array concatenation of the arrays [v1] and [v2]. *) val concat: 'a array list -> 'a array (* Same as [Array.append], but catenates a list of arrays. *) -val sub: 'a array -> int -> int -> 'a array +val sub: 'a array -> pos:int -> len:int -> 'a array (* [Array.sub a start len] returns a fresh array of length [len], containing the elements number [start] to [start + len - 1] of array [a]. @@ -76,12 +76,12 @@ val sub: 'a array -> int -> int -> 'a array val copy: 'a array -> 'a array (* [Array.copy a] returns a copy of [a], that is, a fresh array containing the same elements as [a]. *) -val fill: 'a array -> int -> int -> 'a -> unit +val fill: 'a array -> pos:int -> len:int -> 'a -> unit (* [Array.fill a ofs len x] modifies the array [a] in place, storing [x] in elements number [ofs] to [ofs + len - 1]. Raise [Invalid_argument "Array.fill"] if [ofs] and [len] do not designate a valid subarray of [a]. *) -val blit: 'a array -> int -> 'a array -> int -> int -> unit +val blit: 'a array -> pos:int -> to:'a array -> to_pos:int -> len:int -> unit (* [Array.blit v1 o1 v2 o2 len] copies [len] elements from array [v1], starting at element number [o1], to array [v2], starting at element number [o2]. It works correctly even if @@ -95,24 +95,24 @@ 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 -> unit) -> 'a array -> unit +val iter: fun:('a -> unit) -> 'a array -> unit (* [Array.iter f a] applies function [f] in turn to all 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 +val map: fun:('a -> 'b) -> 'a array -> 'b array (* [Array.map f a] applies function [f] to all the elements of [a], and builds an array with the results returned by [f]: [[| f a.(0); f a.(1); ...; f a.(Array.length a - 1) |]]. *) -val iteri: (int -> 'a -> unit) -> 'a array -> unit -val mapi: (int -> 'a -> 'b) -> 'a array -> 'b array +val iteri: fun:(i:int -> 'a -> unit) -> 'a array -> unit +val mapi: fun:(i:int -> 'a -> 'b) -> 'a array -> 'b array (* Same as [Array.iter] and [Array.map] respectively, but the function is applied to the index of the element as first argument, and the element itself as second argument. *) -val fold_left: ('a -> 'b -> 'a) -> 'a -> 'b array -> 'a +val fold_left: fun:(acc:'a -> 'b -> 'a) -> acc:'a -> 'b array -> 'a (* [Array.fold_left f x a] computes [f (... (f (f x a.(0)) a.(1)) ...) a.(n-1)], where [n] is the length of the array [a]. *) -val fold_right: ('b -> 'a -> 'a) -> 'b array -> 'a -> 'a +val fold_right: fun:('b -> acc:'a -> 'a) -> 'b array -> acc:'a -> 'a (* [Array.fold_right f a x] computes [f a.(0) (f a.(1) ( ... (f a.(n-1) x) ...))], where [n] is the length of the array [a]. *) diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index 5b8499502..8d205cca8 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -52,17 +52,17 @@ val add_char : t -> char -> unit val add_string : t -> string -> unit (* [add_string b s] appends the string [s] at the end of the buffer [b]. *) -val add_substring : t -> string -> int -> int -> unit +val add_substring : t -> string -> pos:int -> len:int -> unit (* [add_substring b s ofs len] takes [len] characters from offset [ofs] in string [s] and appends them at the end of the buffer [b]. *) val add_buffer : t -> t -> unit (* [add_buffer b1 b2] appends the current contents of buffer [b2] at the end of buffer [b1]. [b2] is not modified. *) -val add_channel : t -> in_channel -> int -> unit +val add_channel : t -> in_channel -> len:int -> unit (* [add_channel b ic n] reads exactly [n] character from the input channel [ic] and stores them at the end of buffer [b]. Raise [End_of_file] if the channel contains fewer than [n] characters. *) -val output_buffer : out_channel -> t -> unit +val output_buffer : to:out_channel -> t -> unit (* [output_buffer oc b] writes the current contents of buffer [b] on the output channel [oc]. *) diff --git a/stdlib/digest.mli b/stdlib/digest.mli index 83d48b1e9..2da4560db 100644 --- a/stdlib/digest.mli +++ b/stdlib/digest.mli @@ -23,16 +23,16 @@ type t = string (* The type of digests: 16-character strings. *) val string: string -> t (* Return the digest of the given string. *) -val substring: string -> int -> int -> t +val substring: string -> pos:int -> len:int -> t (* [Digest.substring s ofs len] returns the digest of the substring of [s] starting at character number [ofs] and containing [len] characters. *) -external channel: in_channel -> int -> t = "md5_chan" +external channel: in_channel -> len:int -> t = "md5_chan" (* [Digest.channel ic len] reads [len] characters from channel [ic] and returns their digest. *) val file: string -> t (* Return the digest of the file whose name is given. *) -val output: out_channel -> t -> unit +val output: to:out_channel -> t -> unit (* Write a digest on the given output channel. *) val input: in_channel -> t (* Read a digest from the given input channel. *) diff --git a/stdlib/filename.mli b/stdlib/filename.mli index cf9c931e5..3cc7b41da 100644 --- a/stdlib/filename.mli +++ b/stdlib/filename.mli @@ -29,10 +29,10 @@ val is_implicit : string -> bool with an explicit reference to the current directory ([./] or [../] in Unix), [false] if it starts with an explicit reference to the root directory or the current directory. *) -val check_suffix : string -> string -> bool +val check_suffix : string -> suff:string -> bool (* [check_suffix name suff] returns [true] if the filename [name] ends with the suffix [suff]. *) -val chop_suffix : string -> string -> string +val chop_suffix : string -> suff:string -> string (* [chop_suffix name suff] removes the suffix [suff] from the filename [name]. The behavior is undefined if [name] does not end with the suffix [suff]. *) @@ -49,7 +49,7 @@ val dirname : string -> string current directory to [dirname name] (with [Sys.chdir]), references to [basename name] (which is a relative file name) designate the same file as [name] before the call to [Sys.chdir]. *) -val temp_file: string -> string -> string +val temp_file: prefix:string -> suffix:string -> string (* [temp_file prefix suffix] returns the name of a non-existent temporary file in the temporary directory. The base name of the temporary file is formed by concatenating diff --git a/stdlib/format.mli b/stdlib/format.mli index 988e7bf63..a7c414c85 100644 --- a/stdlib/format.mli +++ b/stdlib/format.mli @@ -224,7 +224,8 @@ val set_formatter_out_channel : out_channel -> unit;; (* Redirect the pretty-printer output to the given channel. *) val set_formatter_output_functions : - (string -> int -> int -> unit) -> (unit -> unit) -> unit;; + out:(buffer:string -> pos:int -> len:int -> unit) -> + flush:(unit -> unit) -> unit;; (* [set_formatter_output_functions out flush] redirects the pretty-printer output to the functions [out] and [flush]. The [out] function performs the pretty-printer output. @@ -234,13 +235,14 @@ val set_formatter_output_functions : called whenever the pretty-printer is flushed using [print_flush] or [print_newline]. *) val get_formatter_output_functions : - unit -> (string -> int -> int -> unit) * (unit -> unit);; + unit -> (buffer:string -> pos:int -> len:int -> unit) * (unit -> unit);; (* Return the current output functions of the pretty-printer. *) (*** Changing the meaning of indentation and line breaking *) val set_all_formatter_output_functions : - (string -> int -> int -> unit) -> (unit -> unit) -> - (unit -> unit) -> (int -> unit) -> unit;; + out:(buffer:string -> pos:int -> len:int -> unit) -> + flush:(unit -> unit) -> + newline:(unit -> unit) -> space:(int -> unit) -> unit;; (* [set_all_formatter_output_functions out flush outnewline outspace] redirects the pretty-printer output to the functions [out] and [flush] as described in @@ -257,7 +259,7 @@ val set_all_formatter_output_functions : [outspace] and [outnewline] are [out (String.make n ' ') 0 n] and [out "\n" 0 1]. *) val get_all_formatter_output_functions : unit -> - (string -> int -> int -> unit) * (unit -> unit) * + (buffer:string -> pos:int -> len:int -> unit) * (unit -> unit) * (unit -> unit) * (int -> unit);; (* Return the current output functions of the pretty-printer, including line breaking and indentation functions. *) diff --git a/stdlib/hashtbl.mli b/stdlib/hashtbl.mli index a5adc958a..c89a8b12a 100644 --- a/stdlib/hashtbl.mli +++ b/stdlib/hashtbl.mli @@ -30,32 +30,32 @@ val create : int -> ('a,'b) t val clear : ('a, 'b) t -> unit (* Empty a hash table. *) -val add : ('a, 'b) t -> 'a -> 'b -> unit +val add : ('a, 'b) t -> key:'a -> data:'b -> unit (* [Hashtbl.add tbl x y] adds a binding of [x] to [y] in table [tbl]. Previous bindings for [x] are not removed, but simply hidden. That is, after performing [Hashtbl.remove tbl x], the previous binding for [x], if any, is restored. (Same behavior as with association lists.) *) -val find : ('a, 'b) t -> 'a -> 'b +val find : ('a, 'b) t -> key:'a -> 'b (* [Hashtbl.find tbl x] returns the current binding of [x] in [tbl], or raises [Not_found] if no such binding exists. *) -val find_all : ('a, 'b) t -> 'a -> 'b list +val find_all : ('a, 'b) t -> key:'a -> 'b list (* [Hashtbl.find_all tbl x] returns the list of all data associated with [x] in [tbl]. The current binding is returned first, then the previous bindings, in reverse order of introduction in the table. *) -val mem : ('a, 'b) t -> 'a -> bool +val mem : ('a, 'b) t -> key:'a -> bool (* [Hashtbl.mem tbl x] checks if [x] is bound in [tbl]. *) -val remove : ('a, 'b) t -> 'a -> unit +val remove : ('a, 'b) t -> key:'a -> unit (* [Hashtbl.remove tbl x] removes the current binding of [x] in [tbl], restoring the previous binding if it exists. It does nothing if [x] is not bound in [tbl]. *) -val iter : ('a -> 'b -> unit) -> ('a, 'b) t -> unit +val iter : fun:(key:'a -> data:'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 @@ -89,12 +89,12 @@ module type S = type 'a t val create: int -> 'a t val clear: 'a t -> unit - val add: 'a t -> key -> 'a -> unit - val remove: 'a t -> key -> unit - val find: 'a t -> key -> 'a - val find_all: 'a t -> key -> 'a list - val mem: 'a t -> key -> bool - val iter: (key -> 'a -> unit) -> 'a t -> unit + val add: 'a t -> key:key -> data:'a -> unit + val remove: 'a t -> key:key -> unit + val find: 'a t -> key:key -> 'a + val find_all: 'a t -> key:key -> 'a list + val mem: 'a t -> key:key -> bool + val iter: fun:(key:key -> data:'a -> unit) -> 'a t -> unit end module Make(H: HashedType): (S with type key = H.t) diff --git a/stdlib/lexing.mli b/stdlib/lexing.mli index 1ee28e6a5..240f83a34 100644 --- a/stdlib/lexing.mli +++ b/stdlib/lexing.mli @@ -40,7 +40,7 @@ val from_string : string -> lexbuf the given string. Reading starts from the first character in the string. An end-of-input condition is generated when the end of the string is reached. *) -val from_function : (string -> int -> int) -> lexbuf +val from_function : (buffer:string -> len:int -> int) -> lexbuf (* Create a lexer buffer with the given function as its reading method. When the scanner needs more characters, it will call the given function, giving it a character string [s] and a character @@ -62,7 +62,7 @@ val from_function : (string -> int -> int) -> lexbuf val lexeme : lexbuf -> string (* [Lexing.lexeme lexbuf] returns the string matched by the regular expression. *) -val lexeme_char : lexbuf -> int -> char +val lexeme_char : lexbuf -> pos:int -> char (* [Lexing.lexeme_char lexbuf i] returns character number [i] in the matched string. *) val lexeme_start : lexbuf -> int diff --git a/stdlib/list.mli b/stdlib/list.mli index 90ba1a2ca..0a6601fee 100644 --- a/stdlib/list.mli +++ b/stdlib/list.mli @@ -33,7 +33,7 @@ val hd : 'a list -> 'a val tl : 'a list -> 'a list (* Return the given list without its first element. Raise [Failure "tl"] if the list is empty. *) -val nth : 'a list -> int -> 'a +val nth : 'a list -> pos:int -> 'a (* Return the n-th element of the given list. The first element (head of the list) is at position 0. Raise [Failure "nth"] if the list is too short. *) @@ -54,47 +54,49 @@ val flatten : 'a list list -> 'a list (** Iterators *) -val iter : ('a -> unit) -> 'a list -> unit +val iter : fun:('a -> unit) -> 'a list -> unit (* [List.iter f [a1; ...; an]] applies function [f] in turn to [a1; ...; an]. It is equivalent to [begin f a1; f a2; ...; f an; () end]. *) -val map : ('a -> 'b) -> 'a list -> 'b list +val map : fun:('a -> 'b) -> 'a list -> 'b list (* [List.map f [a1; ...; an]] applies function [f] to [a1, ..., an], and builds the list [[f a1; ...; f an]] with the results returned by [f]. Not tail-recursive. *) -val rev_map : ('a -> 'b) -> 'a list -> 'b list +val rev_map : fun:('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 more efficient. *) -val fold_left : ('a -> 'b -> 'a) -> 'a -> 'b list -> 'a +val fold_left : fun:(acc:'a -> 'b -> 'a) -> acc:'a -> 'b list -> 'a (* [List.fold_left f a [b1; ...; bn]] is [f (... (f (f a b1) b2) ...) bn]. *) -val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b +val fold_right : fun:('a -> acc:'b -> 'b) -> 'a list -> acc:'b -> 'b (* [List.fold_right f [a1; ...; an] b] is [f a1 (f a2 (... (f an b) ...))]. Not tail-recursive. *) (** Iterators on two lists *) -val iter2 : ('a -> 'b -> unit) -> 'a list -> 'b list -> unit +val iter2 : fun:('a -> 'b -> unit) -> 'a list -> 'b list -> unit (* [List.iter2 f [a1; ...; an] [b1; ...; bn]] calls in turn [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 +val map2 : fun:('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list (* [List.map2 f [a1; ...; an] [b1; ...; bn]] is [[f a1 b1; ...; f an bn]]. Raise [Invalid_argument] if the two lists have different lengths. Not tail-recursive. *) -val rev_map2 : ('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list +val rev_map2 : fun:('a -> 'b -> 'c) -> 'a list -> 'b list -> 'c list (* [List.rev_map2 f l] gives the same result as [List.rev (List.map2 f l)], but is tail-recursive and more efficient. *) -val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b list -> 'c list -> 'a +val fold_left2 : + fun:(acc:'a -> 'b -> 'c -> 'a) -> acc:'a -> 'b list -> 'c list -> 'a (* [List.fold_left2 f a [b1; ...; bn] [c1; ...; cn]] is [f (... (f (f a b1 c1) b2 c2) ...) bn cn]. Raise [Invalid_argument] if the two lists have different lengths. *) -val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> 'c -> 'c +val fold_right2 : + fun:('a -> 'b -> acc:'c -> 'c) -> 'a list -> 'b list -> acc:'c -> 'c (* [List.fold_right2 f [a1; ...; an] [b1; ...; bn] c] is [f a1 b1 (f a2 b2 (... (f an bn c) ...))]. Raise [Invalid_argument] if the two lists have @@ -102,42 +104,42 @@ val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> 'c -> 'c (** List scanning *) -val for_all : ('a -> bool) -> 'a list -> bool +val for_all : pred:('a -> bool) -> 'a list -> bool (* [for_all p [a1; ...; an]] checks if all elements of the list satisfy the predicate [p]. That is, it returns [(p a1) && (p a2) && ... && (p an)]. *) -val exists : ('a -> bool) -> 'a list -> bool +val exists : pred:('a -> bool) -> 'a list -> bool (* [exists p [a1; ...; an]] checks if at least one element of the list satisfies the predicate [p]. That is, it returns [(p a1) || (p a2) || ... || (p an)]. *) -val for_all2 : ('a -> 'b -> bool) -> 'a list -> 'b list -> bool -val exists2 : ('a -> 'b -> bool) -> 'a list -> 'b list -> bool +val for_all2 : pred:('a -> 'b -> bool) -> 'a list -> 'b list -> bool +val exists2 : pred:('a -> 'b -> bool) -> 'a list -> 'b list -> bool (* Same as [for_all] and [exists], but for a two-argument predicate. Raise [Invalid_argument] if the two lists have different lengths. *) -val mem : 'a -> 'a list -> bool +val mem : elt:'a -> 'a list -> bool (* [mem a l] is true if and only if [a] is equal to an element of [l]. *) -val memq : 'a -> 'a list -> bool +val memq : elt:'a -> 'a list -> bool (* Same as [mem], but uses physical equality instead of structural equality to compare list elements. *) (** List searching *) -val find : ('a -> bool) -> 'a list -> 'a +val find : pred:('a -> bool) -> 'a list -> 'a (* [find p l] returns the first element of the list [l] that satisfies the predicate [p]. Raise [Not_found] if there is no value that satisfies [p] in the list [l]. *) -val filter : ('a -> bool) -> 'a list -> 'a list -val find_all : ('a -> bool) -> 'a list -> 'a list +val filter : pred:('a -> bool) -> 'a list -> 'a list +val find_all : pred:('a -> bool) -> 'a list -> 'a list (* [filter p l] returns all the elements of the list [l] that satisfies the predicate [p]. The order of the elements in the input list is preserved. [find_all] is another name for [filter]. *) -val partition : ('a -> bool) -> 'a list -> 'a list * 'a list +val partition : pred:('a -> bool) -> 'a list -> 'a list * 'a list (* [partition p l] returns a pair of lists [(l1, l2)], where [l1] is the list of all the elements of [l] that satisfy the predicate [p], and [l2] is the list of all the @@ -146,30 +148,30 @@ val partition : ('a -> bool) -> 'a list -> 'a list * 'a list (** Association lists *) -val assoc : 'a -> ('a * 'b) list -> 'b +val assoc : key:'a -> ('a * 'b) list -> 'b (* [assoc a l] returns the value associated with key [a] in the list of pairs [l]. That is, [assoc a [ ...; (a,b); ...] = b] if [(a,b)] is the leftmost binding of [a] in list [l]. Raise [Not_found] if there is no value associated with [a] in the list [l]. *) -val assq : 'a -> ('a * 'b) list -> 'b +val assq : key:'a -> ('a * 'b) list -> 'b (* Same as [assoc], but uses physical equality instead of structural equality to compare keys. *) -val mem_assoc : 'a -> ('a * 'b) list -> bool +val mem_assoc : key:'a -> ('a * 'b) list -> bool (* Same as [assoc], but simply return true if a binding exists, and false if no bindings exist for the given key. *) -val mem_assq : 'a -> ('a * 'b) list -> bool +val mem_assq : key:'a -> ('a * 'b) list -> bool (* Same as [mem_assoc], but uses physical equality instead of structural equality to compare keys. *) -val remove_assoc : 'a -> ('a * 'b) list -> ('a * 'b) list +val remove_assoc : key:'a -> ('a * 'b) list -> ('a * 'b) list (* [remove_assoc a l] returns the list of pairs [l] without the first pair with key [a], if any. Not tail-recursive. *) -val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list +val remove_assq : key:'a -> ('a * 'b) list -> ('a * 'b) list (* Same as [remove_assq], but uses physical equality instead of structural equality to compare keys. Not tail-recursive. *) diff --git a/stdlib/map.mli b/stdlib/map.mli index de55d8489..cacae8d03 100644 --- a/stdlib/map.mli +++ b/stdlib/map.mli @@ -44,32 +44,32 @@ module type S = (* The type of maps from type [key] to type ['a]. *) val empty: 'a t (* The empty map. *) - val add: key -> 'a -> 'a t -> 'a t + val add: key:key -> data:'a -> 'a t -> 'a t (* [add x y m] returns a map containing the same bindings as [m], plus a binding of [x] to [y]. If [x] was already bound in [m], its previous binding disappears. *) - val find: key -> 'a t -> 'a + val find: key:key -> 'a t -> 'a (* [find x m] returns the current binding of [x] in [m], or raises [Not_found] if no such binding exists. *) - val remove: key -> 'a t -> 'a t + val remove: key: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 mem: key -> 'a t -> bool + val mem: key:key -> 'a t -> bool (* [mem x m] returns [true] if [m] contains a binding for [m], and [false] otherwise. *) - val iter: (key -> 'a -> unit) -> 'a t -> unit + val iter: fun:(key:key -> data:'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]: bindings hidden by more recent bindings are not passed to [f]. *) - val map: ('a -> 'b) -> 'a t -> 'b t + val map: fun:('a -> 'b) -> 'a t -> 'b t (* [map f m] returns a map with same domain as [m], where the associated value [a] of all bindings of [m] has been replaced by the result of the application of [f] to [a]. The order in which the associated values are passed to [f] is unspecified. *) - val fold: (key -> 'a -> 'b -> 'b) -> 'a t -> 'b -> 'b + val fold: fun:(key:key -> data:'a -> acc:'b -> 'b) -> 'a t -> acc:'b -> 'b (* [fold f m a] computes [(f kN dN ... (f k1 d1 a)...)], where [k1 ... kN] are the keys of all bindings in [m], and [d1 ... dN] are the associated data. diff --git a/stdlib/marshal.mli b/stdlib/marshal.mli index 25e140d92..d55f175e5 100644 --- a/stdlib/marshal.mli +++ b/stdlib/marshal.mli @@ -47,7 +47,7 @@ type extern_flags = | Closures (* Send function closures *) (* The flags to the [Marshal.to_*] functions below. *) -external to_channel: out_channel -> 'a -> extern_flags list -> unit +external to_channel: out_channel -> data:'a -> flags:extern_flags list -> unit = "output_value" (* [Marshal.to_channel chan v flags] writes the representation of [v] on channel [chan]. The [flags] argument is a @@ -78,14 +78,15 @@ external to_channel: out_channel -> 'a -> extern_flags list -> unit at un-marshaling time, using an MD5 digest of the code transmitted along with the code position.) *) -external to_string: 'a -> extern_flags list -> string +external to_string: data:'a -> flags:extern_flags list -> string = "output_value_to_string" (* [Marshal.to_string v flags] returns a string containing the representation of [v] as a sequence of bytes. The [flags] argument has the same meaning as for [Marshal.to_channel]. *) -val to_buffer: string -> int -> int -> 'a -> extern_flags list -> int +val to_buffer: string -> pos:int -> len:int -> + data:'a -> flags:extern_flags list -> int (* [Marshal.to_buffer buff ofs len v flags] marshals the value [v], storing its byte representation in the string [buff], starting at character number [ofs], and writing at most @@ -100,15 +101,15 @@ external from_channel: in_channel -> 'a = "input_value" one of the [Marshal.to_*] functions, and reconstructs and returns the corresponding value.*) -val from_string: string -> int -> 'a +val from_string: string -> pos:int -> 'a (* [Marshal.from_string buff ofs] unmarshals a structured value like [Marshal.from_channel] does, except that the byte representation is not read from a channel, but taken from the string [buff], starting at position [ofs]. *) val header_size : int -val data_size : string -> int -> int -val total_size : string -> int -> int +val data_size : string -> pos:int -> int +val total_size : string -> pos:int -> int (* The bytes representing a marshaled value are composed of a fixed-size header and a variable-sized data part, whose size can be determined from the header. diff --git a/stdlib/obj.mli b/stdlib/obj.mli index a09659654..fb9392efd 100644 --- a/stdlib/obj.mli +++ b/stdlib/obj.mli @@ -24,11 +24,11 @@ external magic : 'a -> 'b = "%identity" external is_block : t -> bool = "obj_is_block" external tag : t -> int = "obj_tag" external size : t -> int = "%obj_size" -external field : t -> int -> t = "%obj_field" -external set_field : t -> int -> t -> unit = "%obj_set_field" -external new_block : int -> int -> t = "obj_block" +external field : t -> pos:int -> t = "%obj_field" +external set_field : t -> pos:int -> t -> unit = "%obj_set_field" +external new_block : int -> len:int -> t = "obj_block" external dup : t -> t = "obj_dup" -external truncate : t -> int -> unit = "obj_truncate" +external truncate : t -> len:int -> unit = "obj_truncate" val no_scan_tag : int val closure_tag : int diff --git a/stdlib/oo.mli b/stdlib/oo.mli index c9ab18c1c..21df77d66 100644 --- a/stdlib/oo.mli +++ b/stdlib/oo.mli @@ -14,7 +14,7 @@ (* Module [Oo]: object-oriented extension *) -val copy : < .. > as 'a -> 'a +val copy : (< .. > as 'a) -> 'a (* [Oo.copy o] returns a copy of object [o], that is a fresh object with the same methods and instance variables as [o] *) diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml index b82edc1ae..5eb21549a 100644 --- a/stdlib/pervasives.ml +++ b/stdlib/pervasives.ml @@ -12,7 +12,7 @@ (* $Id$ *) -type 'a option = None | Some of 'a +(* type 'a option = None | Some of 'a *) (* Exceptions *) diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index 31347340e..73108775f 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -42,7 +42,7 @@ (* The type of arrays whose elements have type ['a]. *) (*- type 'a list = [] | :: of 'a * 'a list *) (* The type of lists whose elements have type ['a]. *) -type 'a option = None | Some of 'a +(* type 'a option = None | Some of 'a *) (* The type of optional values. *) (*- type ('a, 'b, 'c) format *) (* The type of format strings. ['a] is the type of the parameters @@ -440,7 +440,7 @@ val open_out_bin : string -> out_channel so that no translation takes place during writes. On operating systems that do not distinguish between text mode and binary mode, this function behaves like [open_out]. *) -val open_out_gen : open_flag list -> int -> string -> out_channel +val open_out_gen : mode:open_flag list -> perm:int -> string -> out_channel (* [open_out_gen mode rights filename] opens the file named [filename] for writing, as above. The extra argument [mode] specify the opening mode. The extra argument [rights] specifies @@ -451,32 +451,32 @@ val flush : out_channel -> unit performing all pending writes on that channel. Interactive programs must be careful about flushing standard output and standard error at the right time. *) -val output_char : out_channel -> char -> unit +val output_char : to:out_channel -> char -> unit (* Write the character on the given output channel. *) -val output_string : out_channel -> string -> unit +val output_string : to:out_channel -> string -> unit (* Write the string on the given output channel. *) -val output : out_channel -> string -> int -> int -> unit +val output : out_channel -> buffer:string -> pos:int -> len:int -> unit (* [output chan buff ofs len] writes [len] characters from string [buff], starting at offset [ofs], to the output channel [chan]. Raise [Invalid_argument "output"] if [ofs] and [len] do not designate a valid substring of [buff]. *) -val output_byte : out_channel -> int -> unit +val output_byte : to:out_channel -> int -> unit (* Write one 8-bit integer (as the single character with that code) on the given output channel. The given integer is taken modulo 256. *) -val output_binary_int : out_channel -> int -> unit +val output_binary_int : to:out_channel -> int -> unit (* Write one integer in binary format on the given output channel. The only reliable way to read it back is through the [input_binary_int] function. The format is compatible across all machines for a given version of Objective Caml. *) -val output_value : out_channel -> 'a -> unit +val output_value : to:out_channel -> 'a -> unit (* Write the representation of a structured value of any type to a channel. Circularities and sharing inside the value are detected and preserved. The object can be read back, by the function [input_value]. See the description of module [Marshal] for more information. [output_value] is equivalent to [Marshal.to_channel] with an empty list of flags. *) -val seek_out : out_channel -> int -> unit +val seek_out : out_channel -> pos:int -> unit (* [seek_out chan pos] sets the current writing position to [pos] for channel [chan]. This works only for regular files. On files of other kinds (such as terminals, pipes and sockets), @@ -512,7 +512,7 @@ val open_in_bin : string -> in_channel so that no translation takes place during reads. On operating systems that do not distinguish between text mode and binary mode, this function behaves like [open_in]. *) -val open_in_gen : open_flag list -> int -> string -> in_channel +val open_in_gen : mode:open_flag list -> perm:int -> string -> in_channel (* [open_in_gen mode rights filename] opens the file named [filename] for reading, as above. The extra arguments [mode] and [rights] specify the opening mode and file permissions. @@ -526,7 +526,7 @@ val input_line : in_channel -> string all characters read, without the newline character at the end. Raise [End_of_file] if the end of the file is reached at the beginning of line. *) -val input : in_channel -> string -> int -> int -> int +val input : in_channel -> buffer:string -> pos:int -> len:int -> int (* [input chan buff ofs len] attempts to read [len] characters from channel [chan], storing them in string [buff], starting at character number [ofs]. It returns the actual number of characters @@ -537,7 +537,7 @@ val input : in_channel -> string -> int -> int -> int called again to read the remaining characters, if desired. Exception [Invalid_argument "input"] is raised if [ofs] and [len] do not designate a valid substring of [buff]. *) -val really_input : in_channel -> string -> int -> int -> unit +val really_input : in_channel -> buffer:string -> pos:int -> len:int -> unit (* [really_input chan buff ofs len] reads [len] characters from channel [chan], storing them in string [buff], starting at character number [ofs]. Raise [End_of_file] if @@ -559,7 +559,7 @@ val input_value : in_channel -> 'a This function is identical to [Marshal.from_channel]; see the description of module [Marshal] for more information, in particular concerning the lack of type safety. *) -val seek_in : in_channel -> int -> unit +val seek_in : in_channel -> pos:int -> unit (* [seek_in chan pos] sets the current reading position to [pos] for channel [chan]. This works only for regular files. On files of other kinds, the behavior is unspecified. *) diff --git a/stdlib/queue.mli b/stdlib/queue.mli index 867915bd0..c569ae7dc 100644 --- a/stdlib/queue.mli +++ b/stdlib/queue.mli @@ -36,7 +36,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 -> unit) -> 'a t -> unit +val iter: fun:('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. *) diff --git a/stdlib/set.mli b/stdlib/set.mli index cd0d6b97f..058a91146 100644 --- a/stdlib/set.mli +++ b/stdlib/set.mli @@ -46,14 +46,14 @@ module type S = (* The empty set. *) val is_empty: t -> bool (* Test whether a set is empty or not. *) - val mem: elt -> t -> bool + val mem: elt:elt -> t -> bool (* [mem x s] tests whether [x] belongs to the set [s]. *) - val add: elt -> t -> t + val add: elt:elt -> t -> t (* [add x s] returns a set containing all elements of [s], plus [x]. If [x] was already in [s], [s] is returned unchanged. *) val singleton: elt -> t (* [singleton x] returns the one-element set containing only [x]. *) - val remove: elt -> t -> t + val remove: elt:elt -> t -> t (* [remove x s] returns a set containing all elements of [s], except [x]. If [x] was not in [s], [s] is returned unchanged. *) val union: t -> t -> t @@ -69,11 +69,11 @@ 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 -> unit) -> t -> unit + val iter: fun:(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 + val fold: fun:(elt -> acc:'a -> 'a) -> t -> acc:'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 diff --git a/stdlib/sort.mli b/stdlib/sort.mli index dd6abd2e7..413057090 100644 --- a/stdlib/sort.mli +++ b/stdlib/sort.mli @@ -14,19 +14,19 @@ (* Module [Sort]: sorting and merging lists *) -val list : ('a -> 'a -> bool) -> 'a list -> 'a list +val list : order:('a -> 'a -> bool) -> 'a list -> 'a list (* Sort a list in increasing order according to an ordering predicate. The predicate should return [true] if its first argument is less than or equal to its second argument. *) -val array : ('a -> 'a -> bool) -> 'a array -> unit +val array : order:('a -> 'a -> bool) -> 'a array -> unit (* Sort an array in increasing order according to an ordering predicate. The predicate should return [true] if its first argument is less than or equal to its second argument. The array is sorted in place. *) -val merge : ('a -> 'a -> bool) -> 'a list -> 'a list -> 'a list +val merge : order:('a -> 'a -> bool) -> 'a list -> 'a list -> 'a list (* Merge two lists according to the given predicate. Assuming the two argument lists are sorted according to the predicate, [merge] returns a sorted list containing the elements diff --git a/stdlib/stack.mli b/stdlib/stack.mli index 38e42a623..7815657c7 100644 --- a/stdlib/stack.mli +++ b/stdlib/stack.mli @@ -33,7 +33,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 -> unit) -> 'a t -> unit +val iter: fun:('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. *) diff --git a/stdlib/stream.mli b/stdlib/stream.mli index 20495ecbf..31454b570 100644 --- a/stdlib/stream.mli +++ b/stdlib/stream.mli @@ -45,7 +45,7 @@ val of_channel : in_channel -> char t;; (** Stream iterator *) -val iter : ('a -> unit) -> 'a t -> unit;; +val iter : fun:('a -> unit) -> 'a t -> unit;; (* [Stream.iter f s] scans the whole stream s, applying function [f] in turn to each stream element encountered. *) diff --git a/stdlib/string.mli b/stdlib/string.mli index c7d0207be..36928a5ca 100644 --- a/stdlib/string.mli +++ b/stdlib/string.mli @@ -31,32 +31,32 @@ external set : string -> int -> char -> unit = "%string_safe_set" 0 to [(String.length s - 1)]. You can also write [s.[n] <- c] instead of [String.set s n c]. *) -external create : int -> string = "create_string" +external create : len:int -> string = "create_string" (* [String.create n] returns a fresh string of length [n]. The string initially contains arbitrary characters. Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_string_length]. *) -val make : int -> char -> string +val make : len:int -> char -> string (* [String.make n c] returns a fresh string of length [n], filled with the character [c]. Raise [Invalid_argument] if [n <= 0] or [n > Sys.max_string_length]. *) val copy : string -> string (* Return a copy of the given string. *) -val sub : string -> int -> int -> string +val sub : string -> pos:int -> len:int -> string (* [String.sub s start len] returns a fresh string of length [len], containing the characters number [start] to [start + len - 1] of string [s]. Raise [Invalid_argument] if [start] and [len] do not designate a valid substring of [s]; that is, if [start < 0], or [len < 0], or [start + len > String.length s]. *) -val fill : string -> int -> int -> char -> unit +val fill : string -> pos:int -> len:int -> char -> unit (* [String.fill s start len c] modifies string [s] in place, replacing the characters number [start] to [start + len - 1] by [c]. Raise [Invalid_argument] if [start] and [len] do not designate a valid substring of [s]. *) -val blit : string -> int -> string -> int -> int -> unit +val blit : string -> pos:int -> to:string -> to_pos:int -> len:int -> unit (* [String.blit src srcoff dst dstoff len] copies [len] characters from string [src], starting at character number [srcoff], to string [dst], starting at character number [dstoff]. It works @@ -66,7 +66,7 @@ val blit : string -> int -> string -> int -> int -> unit designate a valid substring of [src], or if [dstoff] and [len] do not designate a valid substring of [dst]. *) -val concat : string -> string list -> string +val concat : sep:string -> string list -> string (* [String.concat sep sl] catenates the list of strings [sl], inserting the separator string [sep] between each. *) @@ -75,31 +75,31 @@ val escaped: string -> string by escape sequences, following the lexical conventions of Objective Caml. *) -val index: string -> char -> int +val index: string -> elt:char -> int (* [String.index s c] returns the position of the leftmost occurrence of character [c] in string [s]. Raise [Not_found] if [c] does not occur in [s]. *) -val rindex: string -> char -> int +val rindex: string -> elt:char -> int (* [String.rindex s c] returns the position of the rightmost occurrence of character [c] in string [s]. Raise [Not_found] if [c] does not occur in [s]. *) -val index_from: string -> int -> char -> int -val rindex_from: string -> int -> char -> int +val index_from: string -> pos:int -> elt:char -> int +val rindex_from: string -> pos:int -> elt:char -> int (* Same as [String.index] and [String.rindex], but start searching at the character position given as second argument. [String.index s c] is equivalent to [String.index_from s 0 c], and [String.rindex s c] to [String.rindex_from s (String.length s - 1) c]. *) -val contains : string -> char -> bool +val contains : string -> elt:char -> bool (* [String.contains s c] tests if character [c] appears in the string [s]. *) -val contains_from : string -> int -> char -> bool +val contains_from : string -> pos:int -> elt:char -> bool (* [String.contains_from s start c] tests if character [c] appears in the substring of [s] starting from [start] to the end of [s]. Raise [Invalid_argument] if [start] is not a valid index of [s]. *) -val rcontains_from : string -> int -> char -> bool +val rcontains_from : string -> pos:int -> elt:char -> bool (* [String.rcontains_from s stop c] tests if character [c] appears in the substring of [s] starting from the beginning of [s] to index [stop]. @@ -124,7 +124,8 @@ val uncapitalize: string -> string external unsafe_get : string -> int -> char = "%string_unsafe_get" external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set" -external unsafe_blit : string -> int -> string -> int -> int -> unit - = "blit_string" "noalloc" -external unsafe_fill : string -> int -> int -> char -> unit - = "fill_string" "noalloc" +external unsafe_blit : + string -> pos:int -> to:string -> to_pos:int -> len:int -> unit + = "blit_string" "noalloc" +external unsafe_fill : string -> pos:int -> len:int -> char -> unit + = "fill_string" "noalloc" diff --git a/stdlib/sys.mli b/stdlib/sys.mli index 39fb7e4a4..7583bb9e6 100644 --- a/stdlib/sys.mli +++ b/stdlib/sys.mli @@ -23,7 +23,7 @@ external file_exists: string -> bool = "sys_file_exists" (* Test if a file with the given name exists. *) external remove: string -> unit = "sys_remove" (* Remove the given file name from the file system. *) -external rename : string -> string -> unit = "sys_rename" +external rename : old:string -> new:string -> unit = "sys_rename" (* Rename a file. The first argument is the old name and the second is the new name. *) external getenv: string -> string = "sys_getenv" diff --git a/stdlib/weak.mli b/stdlib/weak.mli index 53c73e3ee..8b8b6b331 100644 --- a/stdlib/weak.mli +++ b/stdlib/weak.mli @@ -22,7 +22,7 @@ type 'a t;; empty if the object was erased by the GC. *) -val create : int -> 'a t;; +val create : len:int -> 'a t;; (* [Weak.create n] returns a new weak array of length [n]. All the pointers are initially empty. *) @@ -30,30 +30,30 @@ val length : 'a t -> int;; (* [Weak.length ar] returns the length (number of elements) of [ar]. *) -val set : 'a t -> int -> 'a option -> unit;; +val set : 'a t -> pos:int -> 'a option -> unit;; (* [Weak.set ar n (Some el)] sets the [n]th cell of [ar] to be a (full) pointer to [el]; [Weak.set ar n None] sets the [n]th cell of [ar] to empty. Raise [Invalid_argument "Weak.set"] if [n] is not in the range 0 to [Weak.length a - 1]. *) -val get : 'a t -> int -> 'a option;; +val get : 'a t -> pos:int -> 'a option;; (* [Weak.get ar n] returns None if the [n]th cell of [ar] is empty, [Some x] (where [x] is the object) if it is full. Raise [Invalid_argument "Weak.get"] if [n] is not in the range 0 to [Weak.length a - 1]. *) -val check: 'a t -> int -> bool;; +val check: 'a t -> pos:int -> bool;; (* [Weak.check ar n] returns [true] if the [n]th cell of [ar] is full, [false] if it is empty. Note that even if [Weak.check ar n] returns [true], a subsequent [Weak.get ar n] can return [None]. *) -val fill: 'a t -> int -> int -> 'a option -> unit;; +val fill: 'a t -> pos:int -> len:int -> 'a option -> unit;; (* [Weak.fill ar ofs len el] sets to [el] all pointers of [ar] from [ofs] to [ofs + len - 1]. Raise [Invalid_argument "Weak.fill"] if [ofs] and [len] do not designate a valid subarray of [a]. *) -val blit : 'a t -> int -> 'a t -> int -> int -> unit;; +val blit : 'a t -> pos:int -> to:'a t -> to_pos:int -> len:int -> unit;; (* [Weak.blit ar1 off1 ar2 off2 len] copies [len] weak pointers from [ar1] (starting at [off1]) to [ar2] (starting at [off2]). It works correctly even if [ar1] and [ar2] are the same. |