uniformization of the warnings at the head of the hidden sections of the .mli
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12243 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
a4f3f01982
commit
f95e7f4a59
|
@ -201,5 +201,7 @@ val fast_sort : ('a -> 'a -> int) -> 'a array -> unit
|
|||
(**/**)
|
||||
(** {6 Undocumented functions} *)
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
|
||||
external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
||||
|
|
|
@ -205,5 +205,7 @@ val fast_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
|
|||
|
||||
(** {6 Undocumented functions} *)
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
|
||||
external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"
|
||||
|
|
|
@ -13,7 +13,9 @@
|
|||
|
||||
(* $Id$ *)
|
||||
|
||||
(* Internals of forcing lazy values *)
|
||||
(** Run-time support for lazy values.
|
||||
All functions in this module are for system use only, not for the
|
||||
casual user. *)
|
||||
|
||||
exception Undefined;;
|
||||
|
||||
|
|
|
@ -13,6 +13,10 @@
|
|||
|
||||
(* $Id$ *)
|
||||
|
||||
(** Run-time support for recursive modules.
|
||||
All functions in this module are for system use only, not for the
|
||||
casual user. *)
|
||||
|
||||
type shape =
|
||||
| Function
|
||||
| Lazy
|
||||
|
|
|
@ -45,4 +45,6 @@ val compare: t -> t -> int
|
|||
|
||||
(**/**)
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
external unsafe_chr : int -> char = "%identity"
|
||||
|
|
|
@ -42,8 +42,8 @@ type 'a t = 'a lazy_t;;
|
|||
|
||||
exception Undefined;;
|
||||
|
||||
external force : 'a t -> 'a = "%lazy_force";;
|
||||
(* val force : 'a t -> 'a ;; *)
|
||||
external force : 'a t -> 'a = "%lazy_force";;
|
||||
(** [force x] forces the suspension [x] and returns its result.
|
||||
If [x] has already been forced, [Lazy.force x] returns the
|
||||
same value again without recomputing it. If it raised an exception,
|
||||
|
|
|
@ -152,7 +152,7 @@ val flush_input : lexbuf -> unit
|
|||
(** {6 } *)
|
||||
|
||||
(** The following definitions are used by the generated scanners only.
|
||||
They are not intended to be used by user programs. *)
|
||||
They are not intended to be used directly by user programs. *)
|
||||
|
||||
val sub_lexeme : lexbuf -> int -> int -> string
|
||||
val sub_lexeme_opt : lexbuf -> int -> int -> string option
|
||||
|
|
|
@ -30,6 +30,9 @@ external id : < .. > -> int = "%field1"
|
|||
*)
|
||||
|
||||
(**/**)
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
(** For internal use (CamlIDL) *)
|
||||
val new_method : string -> CamlinternalOO.tag
|
||||
val public_method_label : string -> CamlinternalOO.tag
|
||||
|
|
|
@ -74,7 +74,7 @@ val set_trace: bool -> bool
|
|||
(** {6 } *)
|
||||
|
||||
(** The following definitions are used by the generated parsers only.
|
||||
They are not intended to be used by user programs. *)
|
||||
They are not intended to be used directly by user programs. *)
|
||||
|
||||
type parser_env
|
||||
|
||||
|
|
|
@ -926,8 +926,7 @@ val at_exit : (unit -> unit) -> unit
|
|||
|
||||
(**/**)
|
||||
|
||||
|
||||
(** {6 For system use only, not for the casual user} *)
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
val valid_float_lexem : string -> string
|
||||
|
||||
|
|
|
@ -27,7 +27,7 @@ val fprintf : out_channel -> ('a, out_channel, unit) format -> 'a
|
|||
|
||||
Conversion specifications have the following form:
|
||||
|
||||
[% \[flags\] \[width\] \[.precision\] type]
|
||||
[% [flags] [width] [.precision] type]
|
||||
|
||||
In short, a conversion specification consists in the [%] character,
|
||||
followed by optional modifiers and a type which is made of one or
|
||||
|
@ -159,7 +159,7 @@ val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b;;
|
|||
|
||||
(**/**)
|
||||
|
||||
(* For OCaml system internal use only. Don't call directly. *)
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
module CamlinternalPr : sig
|
||||
|
||||
|
|
|
@ -75,8 +75,9 @@ module State = struct
|
|||
(* Returns 30 random bits as an integer 0 <= x < 1073741824 *)
|
||||
let bits s =
|
||||
s.idx <- (s.idx + 1) mod 55;
|
||||
let curval = s.st.(s.idx) in
|
||||
let newval = s.st.((s.idx + 24) mod 55)
|
||||
+ (s.st.(s.idx) lxor ((s.st.(s.idx) lsr 25) land 31)) in
|
||||
+ (curval lxor ((curval lsr 25) land 0x1F)) in
|
||||
s.st.(s.idx) <- newval;
|
||||
newval land 0x3FFFFFFF (* land is needed for 64-bit arch *)
|
||||
;;
|
||||
|
|
|
@ -85,7 +85,7 @@ val npeek : int -> 'a t -> 'a list
|
|||
|
||||
(**/**)
|
||||
|
||||
(** {6 For system use only, not for the casual user} *)
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
val iapp : 'a t -> 'a t -> 'a t
|
||||
val icons : 'a -> 'a t -> 'a t
|
||||
|
|
|
@ -223,6 +223,8 @@ val compare: t -> t -> int
|
|||
|
||||
(**/**)
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
external unsafe_get : string -> int -> char = "%string_unsafe_get"
|
||||
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
|
||||
external unsafe_blit :
|
||||
|
|
|
@ -175,6 +175,8 @@ val compare: t -> t -> int
|
|||
|
||||
(**/**)
|
||||
|
||||
(* The following is for system use only. Do not call directly. *)
|
||||
|
||||
external unsafe_get : string -> int -> char = "%string_unsafe_get"
|
||||
external unsafe_set : string -> int -> char -> unit = "%string_unsafe_set"
|
||||
external unsafe_blit :
|
||||
|
|
Loading…
Reference in New Issue