summaryrefslogtreecommitdiffstats
path: root/stdlib/printf.mli
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/printf.mli')
-rw-r--r--stdlib/printf.mli104
1 files changed, 59 insertions, 45 deletions
diff --git a/stdlib/printf.mli b/stdlib/printf.mli
index e197a4821..e8bd7d6c9 100644
--- a/stdlib/printf.mli
+++ b/stdlib/printf.mli
@@ -147,48 +147,62 @@ val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b;;
(**/**)
(* For system use only. Don't call directly. *)
-type index;;
-
-external index_of_int : int -> index = "%identity";;
-
-type ac = {
- mutable ac_rglr : int;
- mutable ac_skip : int;
- mutable ac_rdrs : int;
-};;
-
-val ac_of_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> ac;;
-
-module Sformat : sig
- external unsafe_to_string : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
- = "%identity"
- external length : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int
- = "%string_length"
- external get : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char
- = "%string_safe_get"
- external unsafe_get : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char
- = "%string_unsafe_get"
- val sub : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> int -> string
- val to_string : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
-end
-
-val scan_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
- 'g array ->
- index ->
- int ->
- (index -> string -> int -> 'h) ->
- (index -> 'i -> 'j -> int -> 'h) ->
- (index -> 'k -> int -> 'h) ->
- (index -> int -> 'h) ->
- (index -> ('l, 'm, 'n, 'o, 'p, 'q) format6 -> int -> 'h) -> 'h
-
-val sub_format :
- (('a, 'b, 'c, 'd, 'e, 'f) format6 -> int) ->
- (('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char -> int) ->
- char -> ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> int
-
-val summarize_format_type : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
-
-val kapr :
- (('a, 'b, 'c, 'd, 'e, 'f) format6 -> Obj.t array -> 'g) ->
- ('a, 'b, 'c, 'd, 'e, 'f) format6 -> 'g
+
+module CamlinternalPr : sig
+
+ module Sformat : sig
+ type index;;
+
+ val index_of_int : int -> index;;
+ external int_of_index : index -> int = "%identity";;
+ external unsafe_index_of_int : int -> index = "%identity";;
+
+ val succ_index : index -> index;;
+
+ val sub : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> index -> int -> string;;
+ val to_string : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string;;
+ external length : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int
+ = "%string_length";;
+ external get : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char
+ = "%string_safe_get";;
+ external unsafe_to_string : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
+ = "%identity";;
+ external unsafe_get : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char
+ = "%string_unsafe_get";;
+
+ end;;
+
+ module Tformat : sig
+
+ type ac = {
+ mutable ac_rglr : int;
+ mutable ac_skip : int;
+ mutable ac_rdrs : int;
+ };;
+
+ val ac_of_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> ac;;
+
+ val sub_format :
+ (('a, 'b, 'c, 'd, 'e, 'f) format6 -> int) ->
+ (('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char -> int) ->
+ char -> ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> int
+
+ val summarize_format_type : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
+
+ val scan_format : ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
+ 'g array ->
+ Sformat.index ->
+ int ->
+ (Sformat.index -> string -> int -> 'h) ->
+ (Sformat.index -> 'i -> 'j -> int -> 'h) ->
+ (Sformat.index -> 'k -> int -> 'h) ->
+ (Sformat.index -> int -> 'h) ->
+ (Sformat.index -> ('l, 'm, 'n, 'o, 'p, 'q) format6 -> int -> 'h) -> 'h
+
+ val kapr :
+ (('a, 'b, 'c, 'd, 'e, 'f) format6 -> Obj.t array -> 'g) ->
+ ('a, 'b, 'c, 'd, 'e, 'f) format6 -> 'g
+ end;;
+
+end;;
+