Skip to content

Commit 579eb1e

Browse files
committed
Documentation.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9040 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
1 parent 5dcc6d8 commit 579eb1e

File tree

2 files changed

+19
-7
lines changed

2 files changed

+19
-7
lines changed

stdlib/printf.ml

+9-4
Original file line numberDiff line numberDiff line change
@@ -362,10 +362,15 @@ type positional_specification =
362362
Calling [got_spec] with appropriate arguments, we ``return'' a positional
363363
specification and an index to go on scanning the [fmt] format at hand.
364364
365-
We do not support [*$] specifications, since this would lead to type
366-
checking problems: a [*$] positional specification means ``take the next
367-
argument to [printf] (which must be an integer value)'', name this integer
368-
value $n$; [*$] now designates parameter $n$.
365+
Note that this is optimized for the regular case, i.e. no positional
366+
parameter, since in this case we juste ``return'' the constant
367+
[Spec_none]; in case we have a positional parameter, we ``return'' a
368+
[Spec_index] [positional_specification] which a bit more costly.
369+
370+
Note also that we do not support [*$] specifications, since this would
371+
lead to type checking problems: a [*$] positional specification means
372+
``take the next argument to [printf] (which must be an integer value)'',
373+
name this integer value $n$; [*$] now designates parameter $n$.
369374
370375
Unfortunately, the type of a parameter specified via a [*$] positional
371376
specification should be the type of the corresponding argument to

stdlib/printf.mli

+10-3
Original file line numberDiff line numberDiff line change
@@ -122,6 +122,7 @@ val bprintf : Buffer.t -> ('a, Buffer.t, unit) format -> 'a
122122
(see module {!Buffer}). *)
123123

124124
(** Formatted output functions with continuations. *)
125+
125126
val kfprintf : (out_channel -> 'a) -> out_channel ->
126127
('b, out_channel, unit, 'a) format4 -> 'b;;
127128
(** Same as [fprintf], but instead of returning immediately,
@@ -180,7 +181,10 @@ module CamlinternalPr : sig
180181
val sub_format :
181182
(('a, 'b, 'c, 'd, 'e, 'f) format6 -> int) ->
182183
(('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
184188

185189
val summarize_format_type : ('a, 'b, 'c, 'd, 'e, 'f) format6 -> string
186190

@@ -192,11 +196,14 @@ module CamlinternalPr : sig
192196
(Sformat.index -> 'i -> 'j -> int -> 'h) ->
193197
(Sformat.index -> 'k -> int -> 'h) ->
194198
(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
196201

197202
val kapr :
198203
(('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+
200207
end;;
201208

202209
end;;

0 commit comments

Comments
 (0)