diff options
author | Gabriel Scherer <gabriel.scherer@gmail.com> | 2014-05-12 15:37:37 +0000 |
---|---|---|
committer | Gabriel Scherer <gabriel.scherer@gmail.com> | 2014-05-12 15:37:37 +0000 |
commit | 72669307e837a103476f44eb6680caf424274f92 (patch) | |
tree | e04b94d3726361e39d5f86698178b14089e9d960 /stdlib/printf.mli | |
parent | 9fa17c95a5575341a9dea716f5393f7e5b6e6e51 (diff) |
second part of Benoît Vaugon's format+gadts patch
To finish the bootstrap cycle, run:
make library-cross
make promote
make partialclean
make core
make library-cross
make promote-cross
make partialclean
make ocamlc ocamllex ocamltools
make library-cross
make promote
make partialclean
make core
make compare
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14810 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/printf.mli')
-rw-r--r-- | stdlib/printf.mli | 73 |
1 files changed, 1 insertions, 72 deletions
diff --git a/stdlib/printf.mli b/stdlib/printf.mli index a75a64181..21e28159a 100644 --- a/stdlib/printf.mli +++ b/stdlib/printf.mli @@ -163,76 +163,5 @@ val kbprintf : (Buffer.t -> 'a) -> Buffer.t -> (** Deprecated *) -val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b;; +val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b (** A deprecated synonym for [ksprintf]. *) - -(**/**) - -(* The following is for system use only. Do not call directly. *) - -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 add_int_index : int -> 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 count_printing_arguments_of_format : - ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int;; - - 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;; |