~ubuntu-branches/debian/sid/ocaml/sid

« back to all changes in this revision

Viewing changes to stdlib/printf.mli

  • Committer: Bazaar Package Importer
  • Author(s): Stefano Zacchiroli
  • Date: 2009-02-22 08:49:13 UTC
  • mfrom: (12.1.1 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090222084913-3i0uw2bhd0lgw0ok
* Uploading to unstable
* debian/control: bump dh-ocaml to (>= 0.4) to avoid buggy ocamlinit.mk

Show diffs side-by-side

added added

removed removed

Lines of Context:
11
11
(*                                                                     *)
12
12
(***********************************************************************)
13
13
 
14
 
(* $Id: printf.mli,v 1.54.6.2 2008/01/11 10:50:06 doligez Exp $ *)
 
14
(* $Id: printf.mli,v 1.57 2008/09/27 20:50:01 weis Exp $ *)
15
15
 
16
16
(** Formatted output functions. *)
17
17
 
122
122
   (see module {!Buffer}). *)
123
123
 
124
124
(** Formatted output functions with continuations. *)
 
125
 
125
126
val kfprintf : (out_channel -> 'a) -> out_channel ->
126
127
              ('b, out_channel, unit, 'a) format4 -> 'b;;
127
128
(** Same as [fprintf], but instead of returning immediately,
180
181
    val sub_format :
181
182
        (('a, 'b, 'c, 'd, 'e, 'f) format6 -> int) ->
182
183
        (('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> char -> int) ->
183
 
        char -> ('a, 'b, 'c, 'd, 'e, 'f) format6 -> int -> int
 
184
        char ->
 
185
        ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
 
186
        int ->
 
187
        int
184
188
 
185
189
    val summarize_format_type : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
186
190
 
192
196
        (Sformat.index -> 'i -> 'j -> int -> 'h) ->
193
197
        (Sformat.index -> 'k -> int -> 'h) ->
194
198
        (Sformat.index -> int -> 'h) ->
195
 
        (Sformat.index -> ('l, 'm, 'n, 'o, 'p, 'q) format6 -> int -> 'h) -> 'h
 
199
        (Sformat.index -> ('l, 'm, 'n, 'o, 'p, 'q) format6 -> int -> 'h) ->
 
200
        'h
196
201
 
197
202
    val kapr :
198
203
        (('a, 'b, 'c, 'd, 'e, 'f) format6 -> Obj.t array -> 'g) ->
199
 
        ('a, 'b, 'c, 'd, 'e, 'f) format6 -> 'g
 
204
        ('a, 'b, 'c, 'd, 'e, 'f) format6 ->
 
205
        'g
 
206
 
200
207
  end;;
201
208
 
202
209
end;;
203