diff options
Diffstat (limited to 'stdlib')
-rw-r--r-- | stdlib/arg.ml | 7 | ||||
-rw-r--r-- | stdlib/array.ml | 3 | ||||
-rw-r--r-- | stdlib/camlinternalLazy.ml | 6 | ||||
-rw-r--r-- | stdlib/filename.ml | 3 | ||||
-rw-r--r-- | stdlib/filename.mli | 3 | ||||
-rw-r--r-- | stdlib/format.mli | 2 | ||||
-rw-r--r-- | stdlib/hashtbl.ml | 6 | ||||
-rw-r--r-- | stdlib/headernt.c | 3 | ||||
-rw-r--r-- | stdlib/map.ml | 3 | ||||
-rw-r--r-- | stdlib/moreLabels.mli | 3 | ||||
-rw-r--r-- | stdlib/nativeint.mli | 3 | ||||
-rw-r--r-- | stdlib/parsing.ml | 3 | ||||
-rw-r--r-- | stdlib/printexc.ml | 3 | ||||
-rw-r--r-- | stdlib/printf.ml | 3 | ||||
-rw-r--r-- | stdlib/scanf.ml | 16 |
15 files changed, 42 insertions, 25 deletions
diff --git a/stdlib/arg.ml b/stdlib/arg.ml index 0602f6103..b49c04a13 100644 --- a/stdlib/arg.ml +++ b/stdlib/arg.ml @@ -64,9 +64,10 @@ let make_symlist prefix sep suffix l = let print_spec buf (key, spec, doc) = if String.length doc > 0 then match spec with - | Symbol (l, _) -> bprintf buf " %s %s%s\n" key (make_symlist "{" "|" "}" l) - doc - | _ -> bprintf buf " %s %s\n" key doc + | Symbol (l, _) -> + bprintf buf " %s %s%s\n" key (make_symlist "{" "|" "}" l) doc + | _ -> + bprintf buf " %s %s\n" key doc ;; let help_action () = raise (Stop (Unknown "-help"));; diff --git a/stdlib/array.ml b/stdlib/array.ml index ec633ea1f..68c203315 100644 --- a/stdlib/array.ml +++ b/stdlib/array.ml @@ -23,7 +23,8 @@ external create: int -> 'a -> 'a array = "caml_make_vect" external unsafe_sub : 'a array -> int -> int -> 'a array = "caml_array_sub" external append_prim : 'a array -> 'a array -> 'a array = "caml_array_append" external concat : 'a array list -> 'a array = "caml_array_concat" -external unsafe_blit : 'a array -> int -> 'a array -> int -> int -> unit = "caml_array_blit" +external unsafe_blit : + 'a array -> int -> 'a array -> int -> int -> unit = "caml_array_blit" let init l f = if l = 0 then [||] else diff --git a/stdlib/camlinternalLazy.ml b/stdlib/camlinternalLazy.ml index 5210c0293..dfdb19c74 100644 --- a/stdlib/camlinternalLazy.ml +++ b/stdlib/camlinternalLazy.ml @@ -23,7 +23,8 @@ let force_lazy_block (blk : 'arg lazy_t) = Obj.set_field (Obj.repr blk) 0 raise_undefined; try let result = closure () in - Obj.set_field (Obj.repr blk) 0 (Obj.repr result); (* do set_field BEFORE set_tag *) + (* do set_field BEFORE set_tag *) + Obj.set_field (Obj.repr blk) 0 (Obj.repr result); Obj.set_tag (Obj.repr blk) Obj.forward_tag; result with e -> @@ -36,7 +37,8 @@ let force_val_lazy_block (blk : 'arg lazy_t) = let closure = (Obj.obj (Obj.field (Obj.repr blk) 0) : unit -> 'arg) in Obj.set_field (Obj.repr blk) 0 raise_undefined; let result = closure () in - Obj.set_field (Obj.repr blk) 0 (Obj.repr result); (* do set_field BEFORE set_tag *) + (* do set_field BEFORE set_tag *) + Obj.set_field (Obj.repr blk) 0 (Obj.repr result); Obj.set_tag (Obj.repr blk) (Obj.forward_tag); result ;; diff --git a/stdlib/filename.ml b/stdlib/filename.ml index 3edcb927a..db15169a0 100644 --- a/stdlib/filename.ml +++ b/stdlib/filename.ml @@ -230,7 +230,8 @@ let temp_file ?(temp_dir = !current_temp_dir_name) prefix suffix = if counter >= 1000 then raise e else try_name (counter + 1) in try_name 0 -let open_temp_file ?(mode = [Open_text]) ?(temp_dir = !current_temp_dir_name) prefix suffix = +let open_temp_file ?(mode = [Open_text]) ?(temp_dir = !current_temp_dir_name) + prefix suffix = let rec try_name counter = let name = temp_file_name temp_dir prefix suffix in try diff --git a/stdlib/filename.mli b/stdlib/filename.mli index b275ebbbd..c44c6d954 100644 --- a/stdlib/filename.mli +++ b/stdlib/filename.mli @@ -87,7 +87,8 @@ val temp_file : ?temp_dir: string -> string -> string -> string *) val open_temp_file : - ?mode: open_flag list -> ?temp_dir: string -> string -> string -> string * out_channel + ?mode: open_flag list -> ?temp_dir: string -> string -> string -> + string * out_channel (** Same as {!Filename.temp_file}, but returns both the name of a fresh temporary file, and an output channel opened (atomically) on this file. This function is more secure than [temp_file]: there diff --git a/stdlib/format.mli b/stdlib/format.mli index a594ed54f..d03500e3c 100644 --- a/stdlib/format.mli +++ b/stdlib/format.mli @@ -380,7 +380,7 @@ type formatter_out_functions = { val set_formatter_out_functions: formatter_out_functions -> unit;; (** [set_formatter_out_functions out_funs] - redirects the pretty-printer output to the functions [out_funs.out_string] and + Redirect the pretty-printer output to the functions [out_funs.out_string] and [out_funs.out_flush] as described in [set_formatter_output_functions]. In addition, the pretty-printer function that outputs a newline is set to the function [out_funs.out_newline] and the function that outputs diff --git a/stdlib/hashtbl.ml b/stdlib/hashtbl.ml index 4480f8fce..dcca372a5 100644 --- a/stdlib/hashtbl.ml +++ b/stdlib/hashtbl.ml @@ -13,8 +13,10 @@ (* Hash tables *) -external seeded_hash_param : int -> int -> int -> 'a -> int = "caml_hash" "noalloc" -external old_hash_param : int -> int -> 'a -> int = "caml_hash_univ_param" "noalloc" +external seeded_hash_param : + int -> int -> int -> 'a -> int = "caml_hash" "noalloc" +external old_hash_param : + int -> int -> 'a -> int = "caml_hash_univ_param" "noalloc" let hash x = seeded_hash_param 10 100 0 x let hash_param n1 n2 x = seeded_hash_param n1 n2 0 x diff --git a/stdlib/headernt.c b/stdlib/headernt.c index bb04dbea8..aa113ac9d 100644 --- a/stdlib/headernt.c +++ b/stdlib/headernt.c @@ -155,7 +155,8 @@ void __declspec(noreturn) __cdecl headerentry() DWORD numwritten; errh = GetStdHandle(STD_ERROR_HANDLE); WriteFile(errh, truename, strlen(truename), &numwritten, NULL); - WriteFile(errh, msg_and_length(" not found or is not a bytecode executable file\r\n"), + WriteFile(errh, msg_and_length(" not found or is not a bytecode" + " executable file\r\n"), &numwritten, NULL); ExitProcess(2); #if _MSC_VER >= 1200 diff --git a/stdlib/map.ml b/stdlib/map.ml index 5695fa56c..7d65bc6bc 100644 --- a/stdlib/map.ml +++ b/stdlib/map.ml @@ -27,7 +27,8 @@ module type S = val add: key -> 'a -> 'a t -> 'a t val singleton: key -> 'a -> 'a t val remove: key -> 'a t -> 'a t - val merge: (key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t + val merge: + (key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t val compare: ('a -> 'a -> int) -> 'a t -> 'a t -> int val equal: ('a -> 'a -> bool) -> 'a t -> 'a t -> bool val iter: (key -> 'a -> unit) -> 'a t -> unit diff --git a/stdlib/moreLabels.mli b/stdlib/moreLabels.mli index bc15cb4bf..93f1222cf 100644 --- a/stdlib/moreLabels.mli +++ b/stdlib/moreLabels.mli @@ -105,7 +105,8 @@ module Map : sig val add : key:key -> data:'a -> 'a t -> 'a t val singleton: key -> 'a -> 'a t val remove : key -> 'a t -> 'a t - val merge: f:(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t + val merge: + f:(key -> 'a option -> 'b option -> 'c option) -> 'a t -> 'b t -> 'c t val compare: cmp:('a -> 'a -> int) -> 'a t -> 'a t -> int val equal: cmp:('a -> 'a -> bool) -> 'a t -> 'a t -> bool val iter : f:(key:key -> data:'a -> unit) -> 'a t -> unit diff --git a/stdlib/nativeint.mli b/stdlib/nativeint.mli index aa788f03c..eb2dde2cf 100644 --- a/stdlib/nativeint.mli +++ b/stdlib/nativeint.mli @@ -58,7 +58,8 @@ external rem : nativeint -> nativeint -> nativeint = "%nativeint_mod" (** Integer remainder. If [y] is not zero, the result of [Nativeint.rem x y] satisfies the following properties: [Nativeint.zero <= Nativeint.rem x y < Nativeint.abs y] and - [x = Nativeint.add (Nativeint.mul (Nativeint.div x y) y) (Nativeint.rem x y)]. + [x = Nativeint.add (Nativeint.mul (Nativeint.div x y) y) + (Nativeint.rem x y)]. If [y = 0], [Nativeint.rem x y] raises [Division_by_zero]. *) val succ : nativeint -> nativeint diff --git a/stdlib/parsing.ml b/stdlib/parsing.ml index b78331152..762128244 100644 --- a/stdlib/parsing.ml +++ b/stdlib/parsing.ml @@ -73,7 +73,8 @@ type parser_output = | Call_error_function (* to avoid warnings *) -let _ = [Read_token; Raise_parse_error; Grow_stacks_1; Grow_stacks_2; Compute_semantic_action; Call_error_function] +let _ = [Read_token; Raise_parse_error; Grow_stacks_1; Grow_stacks_2; + Compute_semantic_action; Call_error_function] external parse_engine : parse_tables -> parser_env -> parser_input -> Obj.t -> parser_output diff --git a/stdlib/printexc.ml b/stdlib/printexc.ml index 428396247..be1d8f0f8 100644 --- a/stdlib/printexc.ml +++ b/stdlib/printexc.ml @@ -58,7 +58,8 @@ let to_string x = 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 diff --git a/stdlib/printf.ml b/stdlib/printf.ml index 349f6e364..1797b8e80 100644 --- a/stdlib/printf.ml +++ b/stdlib/printf.ml @@ -77,7 +77,8 @@ let incomplete_format fmt = Sformat.to_string fmt ^ "''") ;; -(* Parses a string conversion to return the specified length and the padding direction. *) +(* Parses a string conversion to return the specified length and the + padding direction. *) let parse_string_conversion sfmt = let rec parse neg i = if i >= String.length sfmt then (0, neg) else diff --git a/stdlib/scanf.ml b/stdlib/scanf.ml index 10cb472ad..ac950e4cb 100644 --- a/stdlib/scanf.ml +++ b/stdlib/scanf.ml @@ -337,13 +337,14 @@ module Scanning : SCANNING = struct let from_ic_close_at_end = from_ic scan_close_at_end;; (* The scanning buffer reading from [Pervasives.stdin]. - One could try to define [stdib] as a scanning buffer reading a character at a - time (no bufferization at all), but unfortunately the top-level - interaction would be wrong. - This is due to some kind of ``race condition'' when reading from [Pervasives.stdin], + One could try to define [stdib] as a scanning buffer reading a character + at a time (no bufferization at all), but unfortunately the top-level + interaction would be wrong. This is due to some kind of + ``race condition'' when reading from [Pervasives.stdin], since the interactive compiler and [scanf] will simultaneously read the - material they need from [Pervasives.stdin]; then, confusion will result from what should - be read by the top-level and what should be read by [scanf]. + material they need from [Pervasives.stdin]; then, confusion will result + from what should be read by the top-level and what should be read + by [scanf]. This is even more complicated by the one character lookahead that [scanf] is sometimes obliged to maintain: the lookahead character will be available for the next ([scanf]) entry, seemingly coming from nowhere. @@ -1349,7 +1350,8 @@ let scan_format ib ef fmt rv f = if i > lim then incomplete_format fmt else match Sformat.get fmt i with | '0' .. '9' as conv -> - let width, i = read_int_literal (decimal_value_of_char conv) (succ i) in + let width, i = + read_int_literal (decimal_value_of_char conv) (succ i) in Some width, i | _ -> None, i |