diff --git a/byterun/interp.c b/byterun/interp.c index 3a750600003e..122fa763f247 100644 --- a/byterun/interp.c +++ b/byterun/interp.c @@ -1140,5 +1140,3 @@ void caml_release_bytecode(code_t prog, asize_t prog_size) { Assert(prog); Assert(prog_size>0); } - -/* eof $Id$ */ diff --git a/stdlib/arg.mli b/stdlib/arg.mli index 8203e83133cb..bc33d239fd52 100644 --- a/stdlib/arg.mli +++ b/stdlib/arg.mli @@ -56,7 +56,7 @@ type spec = | Symbol of string list * (string -> unit) (** Take one of the symbols as argument and call the function with the symbol *) - | Rest of (string -> unit) (** Stop interpreting keywords and call the + | Rest of (string -> unit) (** Stop interpreting keywords and call the function with each remaining argument *) (** The concrete type describing the behavior associated with a keyword. *) diff --git a/stdlib/array.mli b/stdlib/array.mli index 579ab4ac519b..9fb74b06eb86 100644 --- a/stdlib/array.mli +++ b/stdlib/array.mli @@ -22,7 +22,7 @@ external get : 'a array -> int -> 'a = "%array_safe_get" (** [Array.get a n] returns the element number [n] of array [a]. The first element has number 0. The last element has number [Array.length a - 1]. - You can also write [a.(n)] instead of [Array.get a n]. + You can also write [a.(n)] instead of [Array.get a n]. Raise [Invalid_argument "index out of bounds"] if [n] is outside the range 0 to [(Array.length a - 1)]. *) diff --git a/stdlib/arrayLabels.mli b/stdlib/arrayLabels.mli index 20e953647550..7f8750a64e35 100644 --- a/stdlib/arrayLabels.mli +++ b/stdlib/arrayLabels.mli @@ -70,7 +70,8 @@ val make_matrix : dimx:int -> dimy:int -> 'a -> 'a array array size is only [Sys.max_array_length / 2]. *) val create_matrix : dimx:int -> dimy:int -> 'a -> 'a array array -(** @deprecated [Array.create_matrix] is an alias for {!ArrayLabels.make_matrix}. *) +(** @deprecated [Array.create_matrix] is an alias for + {!ArrayLabels.make_matrix}. *) val append : 'a array -> 'a array -> 'a array (** [Array.append v1 v2] returns a fresh array containing the @@ -165,7 +166,7 @@ val sort : cmp:('a -> 'a -> int) -> 'a array -> unit [Array.sort] is guaranteed to run in constant heap space and logarithmic stack space. - + The current implementation uses Heap Sort. It runs in constant stack space. *) diff --git a/stdlib/buffer.ml b/stdlib/buffer.ml index cafec4444c62..2e8dd8c5e35f 100644 --- a/stdlib/buffer.ml +++ b/stdlib/buffer.ml @@ -30,7 +30,7 @@ let create n = let contents b = String.sub b.buffer 0 b.position let sub b ofs len = - if ofs < 0 || len < 0 || ofs > b.position - len + if ofs < 0 || len < 0 || ofs > b.position - len then invalid_arg "Buffer.sub" else begin let r = String.create len in @@ -39,8 +39,8 @@ let sub b ofs len = end ;; -let nth b ofs = - if ofs < 0 || ofs >= b.position then +let nth b ofs = + if ofs < 0 || ofs >= b.position then invalid_arg "Buffer.nth" else String.get b.buffer ofs ;; @@ -87,7 +87,7 @@ let add_string b s = if new_position > b.length then resize b len; String.blit s 0 b.buffer b.position len; b.position <- new_position - + let add_buffer b bs = add_substring b bs.buffer 0 bs.position @@ -122,8 +122,10 @@ let advance_to_non_alpha s start = if i >= lim then lim else match s.[i] with | 'a' .. 'z' | 'A' .. 'Z' | '0' .. '9' | '_' | - 'é'|'à'|'á'|'è'|'ù'|'â'|'ê'|'î'|'ô'|'û'|'ë'|'ï'|'ü'|'ç'| - 'É'|'À'|'Á'|'È'|'Ù'|'Â'|'Ê'|'Î'|'Ô'|'Û'|'Ë'|'Ï'|'Ü'|'Ç' -> + 'é'|'à'|'á'|'è'|'ù'|'â'|'ê'| + 'î'|'ô'|'û'|'ë'|'ï'|'ü'|'ç'| + 'É'|'À'|'Á'|'È'|'Ù'|'Â'|'Ê'| + 'Î'|'Ô'|'Û'|'Ë'|'Ï'|'Ü'|'Ç' -> advance (i + 1) lim | _ -> i in advance start (String.length s);; diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli index 6fc76148adca..d7afbb18331a 100644 --- a/stdlib/buffer.mli +++ b/stdlib/buffer.mli @@ -18,7 +18,7 @@ This module implements string buffers that automatically expand as necessary. It provides accumulative concatenation of strings in quasi-linear time (instead of quadratic time when strings are - concatenated pairwise). + concatenated pairwise). *) type t @@ -104,4 +104,3 @@ val add_channel : t -> in_channel -> int -> unit val output_buffer : out_channel -> t -> unit (** [output_buffer oc b] writes the current contents of buffer [b] on the output channel [oc]. *) - diff --git a/stdlib/callback.mli b/stdlib/callback.mli index 70ba06c78da0..ba2ab7ecb7e4 100644 --- a/stdlib/callback.mli +++ b/stdlib/callback.mli @@ -17,7 +17,7 @@ This module allows Caml values to be registered with the C runtime under a symbolic name, so that C code can later call back registered - Caml functions, or raise registered Caml exceptions. + Caml functions, or raise registered Caml exceptions. *) val register : string -> 'a -> unit diff --git a/stdlib/camlinternalMod.ml b/stdlib/camlinternalMod.ml index 46281c0f3d3a..f41aef7b631d 100644 --- a/stdlib/camlinternalMod.ml +++ b/stdlib/camlinternalMod.ml @@ -57,4 +57,4 @@ let rec update_mod shape o n = assert (Obj.tag n = 0 && Obj.size n >= Array.length comps); for i = 0 to Array.length comps - 1 do update_mod comps.(i) (Obj.field o i) (Obj.field n i) - done + done diff --git a/stdlib/camlinternalOO.ml b/stdlib/camlinternalOO.ml index 693c1cf3b7d0..7714b5c841f4 100644 --- a/stdlib/camlinternalOO.ml +++ b/stdlib/camlinternalOO.ml @@ -41,7 +41,7 @@ type params = { mutable clean_when_copying : bool; mutable retry_count : int; mutable bucket_small_size : int - } + } let params = { compact_table = true; @@ -49,7 +49,7 @@ let params = { clean_when_copying = true; retry_count = 3; bucket_small_size = 16 -} +} (**** Parameters ****) diff --git a/stdlib/camlinternalOO.mli b/stdlib/camlinternalOO.mli index 51b84871a4bd..734096755cba 100644 --- a/stdlib/camlinternalOO.mli +++ b/stdlib/camlinternalOO.mli @@ -146,7 +146,7 @@ val params : params (** {6 Statistics} *) type stats = - { classes : int; - methods : int; + { classes : int; + methods : int; inst_vars : int } val stats : unit -> stats diff --git a/stdlib/char.mli b/stdlib/char.mli index 29845da4dca8..8ab72bd9a60f 100644 --- a/stdlib/char.mli +++ b/stdlib/char.mli @@ -17,7 +17,7 @@ external code : char -> int = "%identity" (** Return the ASCII code of the argument. *) - + val chr : int -> char (** Return the character with the given ASCII code. Raise [Invalid_argument "Char.chr"] if the argument is diff --git a/stdlib/complex.ml b/stdlib/complex.ml index 3095534baba2..3c28a58b7909 100644 --- a/stdlib/complex.ml +++ b/stdlib/complex.ml @@ -62,20 +62,20 @@ let arg x = atan2 x.im x.re let polar n a = { re = cos a *. n; im = sin a *. n } -let sqrt x = +let sqrt x = if x.re = 0.0 && x.im = 0.0 then { re = 0.0; im = 0.0 } else begin let r = abs_float x.re and i = abs_float x.im in let w = if r >= i then begin - let q = i /. r in - sqrt(r) *. sqrt(0.5 *. (1.0 +. sqrt(1.0 +. q *. q))) + let q = i /. r in + sqrt(r) *. sqrt(0.5 *. (1.0 +. sqrt(1.0 +. q *. q))) end else begin let q = r /. i in sqrt(i) *. sqrt(0.5 *. (q +. sqrt(1.0 +. q *. q))) - end in + end in if x.re >= 0.0 - then { re = w; im = 0.5 *. x.im /. w } + then { re = w; im = 0.5 *. x.im /. w } else { re = 0.5 *. i /. w; im = if x.im >= 0.0 then w else -. w } end diff --git a/stdlib/complex.mli b/stdlib/complex.mli index 0fc3696f580e..3c3b361d27e4 100644 --- a/stdlib/complex.mli +++ b/stdlib/complex.mli @@ -73,7 +73,7 @@ val arg: t -> float negative real axis. *) val polar: float -> float -> t -(** [polar norm arg] returns the complex having norm [norm] +(** [polar norm arg] returns the complex having norm [norm] and argument [arg]. *) val exp: t -> t diff --git a/stdlib/digest.mli b/stdlib/digest.mli index 72db79948f0c..981bd02fc3e8 100644 --- a/stdlib/digest.mli +++ b/stdlib/digest.mli @@ -18,7 +18,7 @@ This module provides functions to compute 128-bit ``digests'' of arbitrary-length strings or files. The digests are of cryptographic quality: it is very hard, given a digest, to forge a string having - that digest. The algorithm used is MD5. + that digest. The algorithm used is MD5. *) type t = string diff --git a/stdlib/filename.ml b/stdlib/filename.ml index e655e10ca128..62cb63951dbb 100644 --- a/stdlib/filename.ml +++ b/stdlib/filename.ml @@ -42,7 +42,7 @@ module Unix = struct (String.length suff) = suff let temporary_directory = try Sys.getenv "TMPDIR" with Not_found -> "/tmp" - let quote = generic_quote "'\\''" + let quote = generic_quote "'\\''" end module Win32 = struct @@ -106,17 +106,17 @@ let (current_dir_name, parent_dir_name, dir_sep, is_dir_sep, rindex_dir_sep, is_relative, is_implicit, check_suffix, temporary_directory, quote) = match Sys.os_type with "Unix" -> - (Unix.current_dir_name, Unix.parent_dir_name, Unix.dir_sep, + (Unix.current_dir_name, Unix.parent_dir_name, Unix.dir_sep, Unix.is_dir_sep, Unix.rindex_dir_sep, Unix.is_relative, Unix.is_implicit, Unix.check_suffix, Unix.temporary_directory, Unix.quote) | "Win32" -> - (Win32.current_dir_name, Win32.parent_dir_name, Win32.dir_sep, + (Win32.current_dir_name, Win32.parent_dir_name, Win32.dir_sep, Win32.is_dir_sep, Win32.rindex_dir_sep, Win32.is_relative, Win32.is_implicit, Win32.check_suffix, Win32.temporary_directory, Win32.quote) | "Cygwin" -> - (Cygwin.current_dir_name, Cygwin.parent_dir_name, Cygwin.dir_sep, + (Cygwin.current_dir_name, Cygwin.parent_dir_name, Cygwin.dir_sep, Cygwin.is_dir_sep, Cygwin.rindex_dir_sep, Cygwin.is_relative, Cygwin.is_implicit, Cygwin.check_suffix, Cygwin.temporary_directory, Cygwin.quote) diff --git a/stdlib/filename.mli b/stdlib/filename.mli index ed63a45fd546..9b98bc74f7ad 100644 --- a/stdlib/filename.mli +++ b/stdlib/filename.mli @@ -97,4 +97,3 @@ val quote : string -> string (** Return a quoted version of a file name, suitable for use as one argument in a shell command line, escaping all shell meta-characters. *) - diff --git a/stdlib/format.mli b/stdlib/format.mli index 18100614353c..27801ee76849 100644 --- a/stdlib/format.mli +++ b/stdlib/format.mli @@ -403,7 +403,8 @@ val get_formatter_tag_functions : unit -> formatter_tag_functions;; (** Return the current tag functions of the pretty-printer. *) -(** {6 Changing the meaning of pretty printing (indentation, line breaking, and printing material)} *) +(** {6 Changing the meaning of pretty printing (indentation, line breaking, + and printing material)} *) val set_all_formatter_output_functions : out:(string -> int -> int -> unit) -> diff --git a/stdlib/gc.mli b/stdlib/gc.mli index c02695d4ae48..4d36a29f2e83 100644 --- a/stdlib/gc.mli +++ b/stdlib/gc.mli @@ -16,7 +16,7 @@ (** Memory management control and statistics; finalised values. *) type stat = - { minor_words : float; + { minor_words : float; (** Number of words allocated in the minor heap since the program was started. This number is accurate in byte-code programs, but only an approximation in programs @@ -208,7 +208,7 @@ val finalise : ('a -> unit) -> 'a -> unit Instead you should write: - [ let f = fun x -> ... ;; let v = ... in Gc.finalise f v ] - + The [f] function can use all features of O'Caml, including assignments that make the value reachable again. It can also @@ -219,7 +219,7 @@ val finalise : ('a -> unit) -> 'a -> unit the exception will interrupt whatever the program was doing when the function was called. - + [finalise] will raise [Invalid_argument] if [v] is not heap-allocated. Some examples of values that are not heap-allocated are integers, constant constructors, booleans, @@ -233,7 +233,7 @@ val finalise : ('a -> unit) -> 'a -> unit stored into arrays, so they can be finalised and collected while another copy is still in use by the program. - + The results of calling {!String.make}, {!String.create}, {!Array.make}, and {!Pervasives.ref} are guaranteed to be heap-allocated and non-constant except when the length argument is [0]. diff --git a/stdlib/genlex.mli b/stdlib/genlex.mli index 7ac0b647b604..93bc5f55e8ca 100644 --- a/stdlib/genlex.mli +++ b/stdlib/genlex.mli @@ -19,7 +19,7 @@ This module implements a simple ``standard'' lexical analyzer, presented as a function from character streams to token streams. It implements roughly the lexical conventions of Caml, but is parameterized by the - set of keywords of your language. + set of keywords of your language. Example: a lexer suitable for a desk calculator is obtained by @@ -54,7 +54,7 @@ type token = | Float of float | String of string | Char of char - + val make_lexer : string list -> char Stream.t -> token Stream.t (** Construct the lexer function. The first argument is the list of keywords. An identifier [s] is returned as [Kwd s] if [s] @@ -64,5 +64,3 @@ val make_lexer : string list -> char Stream.t -> token Stream.t [Parse_error]) otherwise. Blanks and newlines are skipped. Comments delimited by [(*] and [*)] are skipped as well, and can be nested. *) - - diff --git a/stdlib/hashtbl.ml b/stdlib/hashtbl.ml index 225aa6be78ee..bcb2c9275a66 100644 --- a/stdlib/hashtbl.ml +++ b/stdlib/hashtbl.ml @@ -277,5 +277,3 @@ module Make(H: HashedType): (S with type key = H.t) = let fold = fold let length = length end - -(* eof $Id$ *) diff --git a/stdlib/int32.mli b/stdlib/int32.mli index 3408d0e9ff73..dc733ec9fc06 100644 --- a/stdlib/int32.mli +++ b/stdlib/int32.mli @@ -166,4 +166,3 @@ external format : string -> int32 -> string = "caml_int32_format" one [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification. This function is deprecated; use {!Printf.sprintf} with a [%lx] format instead. *) - diff --git a/stdlib/int64.mli b/stdlib/int64.mli index da5f5de1b75d..7bc39e61231b 100644 --- a/stdlib/int64.mli +++ b/stdlib/int64.mli @@ -188,4 +188,3 @@ external format : string -> int64 -> string = "caml_int64_format" [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification. This function is deprecated; use {!Printf.sprintf} with a [%Lx] format instead. *) - diff --git a/stdlib/lexing.ml b/stdlib/lexing.ml index 0211144efc09..8aec2ef124af 100644 --- a/stdlib/lexing.ml +++ b/stdlib/lexing.ml @@ -53,7 +53,7 @@ type lex_tables = lex_base_code : string; lex_backtrk_code : string; lex_default_code : string; - lex_trans_code : string; + lex_trans_code : string; lex_check_code : string; lex_code: string;} @@ -96,7 +96,7 @@ let lex_refill read_fun aux_buffer lexbuf = *) if lexbuf.lex_buffer_len + n > String.length lexbuf.lex_buffer then begin (* There is not enough space at the end of the buffer *) - if lexbuf.lex_buffer_len - lexbuf.lex_start_pos + n + if lexbuf.lex_buffer_len - lexbuf.lex_start_pos + n <= String.length lexbuf.lex_buffer then begin (* But there is enough space if we reclaim the junk at the beginning diff --git a/stdlib/lexing.mli b/stdlib/lexing.mli index 09664377686a..ffa85f7961da 100644 --- a/stdlib/lexing.mli +++ b/stdlib/lexing.mli @@ -152,7 +152,7 @@ type lex_tables = lex_base_code : string; lex_backtrk_code : string; lex_default_code : string; - lex_trans_code : string; + lex_trans_code : string; lex_check_code : string; lex_code: string;} diff --git a/stdlib/list.ml b/stdlib/list.ml index f7846df199f2..fe0b3beff587 100644 --- a/stdlib/list.ml +++ b/stdlib/list.ml @@ -158,7 +158,8 @@ let rec mem_assq x = function let rec remove_assoc x = function | [] -> [] - | (a, b as pair) :: l -> if compare a x = 0 then l else pair :: remove_assoc x l + | (a, b as pair) :: l -> + if compare a x = 0 then l else pair :: remove_assoc x l let rec remove_assq x = function | [] -> [] diff --git a/stdlib/list.mli b/stdlib/list.mli index 8e2da4caf71a..e3567516f0a7 100644 --- a/stdlib/list.mli +++ b/stdlib/list.mli @@ -247,7 +247,7 @@ val sort : ('a -> 'a -> int) -> 'a list -> 'a list [List.sort] is guaranteed to run in constant heap space (in addition to the size of the result list) and logarithmic stack space. - + The current implementation uses Merge Sort. It runs in constant heap space and logarithmic stack space. *) @@ -256,7 +256,7 @@ val stable_sort : ('a -> 'a -> int) -> 'a list -> 'a list (** Same as {!List.sort}, but the sorting algorithm is guaranteed to be stable (i.e. elements that compare equal are kept in their original order) . - + The current implementation uses Merge Sort. It runs in constant heap space and logarithmic stack space. *) diff --git a/stdlib/listLabels.mli b/stdlib/listLabels.mli index 2f9a3787901b..1cf43ee09c58 100644 --- a/stdlib/listLabels.mli +++ b/stdlib/listLabels.mli @@ -256,14 +256,14 @@ val sort : cmp:('a -> 'a -> int) -> 'a list -> 'a list [List.sort] is guaranteed to run in constant heap space (in addition to the size of the result list) and logarithmic stack space. - + The current implementation uses Merge Sort and is the same as {!ListLabels.stable_sort}. *) val stable_sort : cmp:('a -> 'a -> int) -> 'a list -> 'a list (** Same as {!ListLabels.sort}, but the sorting algorithm is stable. - + The current implementation is Merge Sort. It runs in constant heap space and logarithmic stack space. *) diff --git a/stdlib/map.mli b/stdlib/map.mli index 71d6e269c18c..ca8241303642 100644 --- a/stdlib/map.mli +++ b/stdlib/map.mli @@ -20,10 +20,10 @@ over the keys. All operations over maps are purely applicative (no side-effects). The implementation uses balanced binary trees, and therefore searching - and insertion take time logarithmic in the size of the map. + and insertion take time logarithmic in the size of the map. *) -module type OrderedType = +module type OrderedType = sig type t (** The type of the map keys. *) @@ -109,4 +109,3 @@ module type S = module Make (Ord : OrderedType) : S with type key = Ord.t (** Functor building an implementation of the map structure given a totally ordered type. *) - diff --git a/stdlib/marshal.ml b/stdlib/marshal.ml index 599e8606653c..0410a23e991d 100644 --- a/stdlib/marshal.ml +++ b/stdlib/marshal.ml @@ -50,4 +50,4 @@ let from_string buff ofs = if ofs > String.length buff - (header_size + len) then invalid_arg "Marshal.from_string" else from_string_unsafe buff ofs - end + end diff --git a/stdlib/marshal.mli b/stdlib/marshal.mli index 0e42369d458b..ac0775bb1687 100644 --- a/stdlib/marshal.mli +++ b/stdlib/marshal.mli @@ -41,7 +41,7 @@ and [Marshal.from_channel] must be opened in binary mode, using e.g. [open_out_bin] or [open_in_bin]; channels opened in text mode will cause unmarshaling errors on platforms where text channels behave - differently than binary channels, e.g. Windows. + differently than binary channels, e.g. Windows. *) type extern_flags = @@ -54,8 +54,8 @@ val to_channel : out_channel -> 'a -> extern_flags list -> unit of [v] on channel [chan]. The [flags] argument is a possibly empty list of flags that governs the marshaling behavior with respect to sharing and functional values. - - If [flags] does not contain [Marshal.No_sharing], circularities + + If [flags] does not contain [Marshal.No_sharing], circularities and sharing inside the value [v] are detected and preserved in the sequence of bytes produced. In particular, this guarantees that marshaling always terminates. Sharing @@ -66,7 +66,7 @@ val to_channel : out_channel -> 'a -> extern_flags list -> unit substructures, but may cause slower marshaling and larger byte representations if [v] actually contains sharing, or even non-termination if [v] contains cycles. - + If [flags] does not contain [Marshal.Closures], marshaling fails when it encounters a functional value inside [v]: only ``pure'' data structures, containing neither @@ -119,7 +119,7 @@ val header_size : int in characters, of the marshaled value. Both {!Marshal.data_size} and {!Marshal.total_size} raise [Failure] if [buff], [ofs] does not contain a valid header. - + To read the byte representation of a marshaled value into a string buffer, the program needs to read first {!Marshal.header_size} characters into the buffer, @@ -134,5 +134,3 @@ val data_size : string -> int -> int val total_size : string -> int -> int (** See {!Marshal.header_size}.*) - - diff --git a/stdlib/nativeint.mli b/stdlib/nativeint.mli index de144310f7d9..ff499a26f8ab 100644 --- a/stdlib/nativeint.mli +++ b/stdlib/nativeint.mli @@ -27,7 +27,7 @@ space than values of type [int], and arithmetic operations on [nativeint] are generally slower than those on [int]. Use [nativeint] only when the application requires the extra bit of precision - over the [int] type. + over the [int] type. *) val zero : nativeint @@ -52,7 +52,7 @@ external mul : nativeint -> nativeint -> nativeint = "%nativeint_mul" (** Multiplication. *) external div : nativeint -> nativeint -> nativeint = "%nativeint_div" -(** Integer division. Raise [Division_by_zero] if the second +(** Integer division. Raise [Division_by_zero] if the second argument is zero. This division rounds the real quotient of its arguments towards zero, as specified for {!Pervasives.(/)}. *) @@ -136,7 +136,7 @@ external of_float : float -> nativeint = "caml_nativeint_of_float" The result of the conversion is undefined if, after truncation, the number is outside the range \[{!Nativeint.min_int}, {!Nativeint.max_int}\]. *) - + external to_float : nativeint -> float = "caml_nativeint_to_float" (** Convert the given native integer to a floating-point number. *) @@ -183,4 +183,3 @@ external format : string -> nativeint -> string = "caml_nativeint_format" one [%d], [%i], [%u], [%x], [%X] or [%o] conversion specification. This function is deprecated; use {!Printf.sprintf} with a [%nx] format instead. *) - diff --git a/stdlib/obj.mli b/stdlib/obj.mli index 29025a213b5e..44556125639e 100644 --- a/stdlib/obj.mli +++ b/stdlib/obj.mli @@ -55,4 +55,3 @@ val out_of_heap_tag : int val marshal : t -> string val unmarshal : string -> int -> t * int - diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml index 5a7fdbbccce0..6db313d93b88 100644 --- a/stdlib/pervasives.ml +++ b/stdlib/pervasives.ml @@ -120,7 +120,7 @@ let min_float = float_of_bits 0x00_10_00_00_00_00_00_00L let epsilon_float = float_of_bits 0x3C_B0_00_00_00_00_00_00L - + type fpclass = FP_normal | FP_subnormal @@ -234,10 +234,10 @@ let open_out_bin name = external flush : out_channel -> unit = "caml_ml_flush" -external out_channels_list : unit -> out_channel list +external out_channels_list : unit -> out_channel list = "caml_ml_out_channels_list" -let flush_all () = +let flush_all () = let rec iter = function [] -> () | a::l -> (try flush a with _ -> ()); iter l @@ -287,7 +287,7 @@ let open_in_bin name = external input_char : in_channel -> char = "caml_ml_input_char" -external unsafe_input : in_channel -> string -> int -> int -> int +external unsafe_input : in_channel -> string -> int -> int -> int = "caml_ml_input" let input ic s ofs len = @@ -329,7 +329,7 @@ let input_line chan = ignore (input_char chan); (* skip the newline *) match accu with [] -> res - | _ -> let len = len + n - 1 in + | _ -> let len = len + n - 1 in build_result (string_create len) len (res :: accu) end else begin (* n < 0: newline not found *) let beg = string_create (-n) in diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index 1e7814403e33..1af15bd4acd5 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -28,7 +28,7 @@ external raise : exn -> 'a = "%raise" (** Raise the given exception value *) - + val invalid_arg : string -> 'a (** Raise exception [Invalid_argument] with the given string. *) @@ -216,7 +216,7 @@ external ( asr ) : int -> int -> int = "%asrint" (** [n asr m] shifts [n] to the right by [m] bits. This is an arithmetic shift: the sign bit of [n] is replicated. The result is unspecified if [m < 0] or [m >= bitsize]. *) - + (** {6 Floating-point arithmetic} @@ -228,8 +228,8 @@ external ( asr ) : int -> int -> int = "%asrint" [neg_infinity] for [-1.0 /. 0.0], and [nan] (``not a number'') for [0.0 /. 0.0]. These special numbers then propagate through floating-point computations as expected: for instance, - [1.0 /. infinity] is [0.0], and any operation with [nan] as - argument returns [nan] as result. + [1.0 /. infinity] is [0.0], and any operation with [nan] as + argument returns [nan] as result. *) external ( ~-. ) : float -> float = "%negfloat" @@ -451,7 +451,7 @@ external snd : 'a * 'b -> 'b = "%field1" (** {6 List operations} - More list operations are provided in module {!List}. + More list operations are provided in module {!List}. *) val ( @ ) : 'a list -> 'a list -> 'a list @@ -554,8 +554,9 @@ type open_flag = | Open_binary (** open in binary mode (no conversion). *) | Open_text (** open in text mode (may perform conversions). *) | Open_nonblock (** open in non-blocking mode. *) -(** Opening modes for {!Pervasives.open_out_gen} and {!Pervasives.open_in_gen}. *) - +(** Opening modes for {!Pervasives.open_out_gen} and + {!Pervasives.open_in_gen}. *) + val open_out : string -> out_channel (** Open the named file for writing, and return a new output channel on that file, positionned at the beginning of the file. The @@ -578,7 +579,7 @@ val open_out_gen : open_flag list -> int -> string -> out_channel cases of this function. *) val flush : out_channel -> unit -(** Flush the buffer associated with the given output channel, +(** Flush the buffer associated with the given output channel, performing all pending writes on that channel. Interactive programs must be careful about flushing standard output and standard error at the right time. *) @@ -703,7 +704,7 @@ val input : in_channel -> string -> int -> int -> int if desired. (See also {!Pervasives.really_input} for reading exactly [len] characters.) Exception [Invalid_argument "input"] is raised if [pos] and [len] - do not designate a valid substring of [buf]. *) + do not designate a valid substring of [buf]. *) val really_input : in_channel -> string -> int -> int -> unit (** [really_input ic buf pos len] reads [len] characters from channel [ic], @@ -813,7 +814,7 @@ external decr : int ref -> unit = "%decr" (** {6 Operations on format strings} *) -(** See modules {!Printf} and {!Scanf} for more operations on +(** See modules {!Printf} and {!Scanf} for more operations on format strings. *) type ('a, 'b, 'c) format = ('a, 'b, 'c, 'c) format4 diff --git a/stdlib/printexc.mli b/stdlib/printexc.mli index cb012f2e7eff..887169c4292c 100644 --- a/stdlib/printexc.mli +++ b/stdlib/printexc.mli @@ -36,4 +36,3 @@ val catch : ('a -> 'b) -> 'a -> 'b makes it harder to track the location of the exception using the debugger or the stack backtrace facility. So, do not use [Printexc.catch] in new code. *) - diff --git a/stdlib/printf.ml b/stdlib/printf.ml index 43859d5912e8..1e4f0d66c2b7 100644 --- a/stdlib/printf.ml +++ b/stdlib/printf.ml @@ -283,7 +283,7 @@ let scan_positional fmt scan_flags n i = [cont_s] for outputting a string (args: string, next pos) [cont_a] for performing a %a action (args: fn, arg, next pos) [cont_t] for performing a %t action (args: fn, next pos) - [cont_f] for performing a flush action + [cont_f] for performing a flush action [cont_m] for performing a %( action (args: sfmt, next pos) "next pos" is the position in [fmt] of the first character following the %format in [fmt]. *) diff --git a/stdlib/sort.ml b/stdlib/sort.ml index a09b6d8414fc..7c53ab777499 100644 --- a/stdlib/sort.ml +++ b/stdlib/sort.ml @@ -97,4 +97,3 @@ let array cmp arr = unsafe_set arr !j val_i end done - diff --git a/stdlib/sort.mli b/stdlib/sort.mli index 2879edfe3703..7069052eb471 100644 --- a/stdlib/sort.mli +++ b/stdlib/sort.mli @@ -39,4 +39,3 @@ val merge : ('a -> 'a -> bool) -> 'a list -> 'a list -> 'a list predicate, [merge] returns a sorted list containing the elements from the two lists. The behavior is undefined if the two argument lists were not sorted. *) - diff --git a/stdlib/stack.mli b/stdlib/stack.mli index 50a46ed04ce6..bf33d01aba95 100644 --- a/stdlib/stack.mli +++ b/stdlib/stack.mli @@ -15,7 +15,7 @@ (** Last-in first-out stacks. - This module implements stacks (LIFOs), with in-place modification. + This module implements stacks (LIFOs), with in-place modification. *) type 'a t @@ -55,4 +55,3 @@ 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. *) - diff --git a/stdlib/stream.mli b/stdlib/stream.mli index 13396df44102..28cfd3a1c4e9 100644 --- a/stdlib/stream.mli +++ b/stdlib/stream.mli @@ -31,7 +31,7 @@ exception Error of string Warning: these functions create streams with fast access; it is illegal to mix them with streams built with [[< >]]; would raise [Failure] - when accessing such mixed streams. + when accessing such mixed streams. *) val from : (int -> 'a option) -> 'a t diff --git a/stdlib/sys.mli b/stdlib/sys.mli index 920dc985739f..72e0c9e4e82e 100644 --- a/stdlib/sys.mli +++ b/stdlib/sys.mli @@ -112,7 +112,7 @@ val set_signal : int -> signal_behavior -> unit (** Same as {!Sys.signal} but return value is ignored. *) -(** {7 Signal numbers for the standard POSIX signals.} *) +(** {7 Signal numbers for the standard POSIX signals.} *) val sigabrt : int (** Abnormal termination *) @@ -185,7 +185,7 @@ exception Break val catch_break : bool -> unit (** [catch_break] governs whether interactive interrupt (ctrl-C) - terminates the program or raises the [Break] exception. + terminates the program or raises the [Break] exception. Call [catch_break true] to enable raising [Break], and [catch_break false] to let the system terminate the program on user interrupt. *)