summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/buffer.ml8
-rw-r--r--stdlib/buffer.mli20
-rw-r--r--stdlib/printf.mli18
3 files changed, 21 insertions, 25 deletions
diff --git a/stdlib/buffer.ml b/stdlib/buffer.ml
index ce9b5c1f1..dcde111ec 100644
--- a/stdlib/buffer.ml
+++ b/stdlib/buffer.ml
@@ -89,7 +89,7 @@ let closing = function
(* opening and closing: open and close characters, typically ( and )
k balance of opening and closing chars
s the string where we are searching
- p the index where we start the search *)
+ start the index where we start the search *)
let advance_to_closing opening closing k s start =
let rec advance k i lim =
if i >= lim then raise Not_found else
@@ -110,7 +110,7 @@ let advance_to_non_alpha s start =
| _ -> i in
advance start (String.length s);;
-(* We are just at the beginning of an ident in s, starting at p *)
+(* We are just at the beginning of an ident in s, starting at start *)
let find_ident s start =
match s.[start] with
(* Parenthesized ident ? *)
@@ -123,8 +123,8 @@ let find_ident s start =
let stop = advance_to_non_alpha s (start + 1) in
String.sub s start (stop - start), stop;;
-(* Substitute $ident (or $(ident)) in s,
- according to the function f. *)
+(* Substitute $ident, $(ident), or ${ident} in s,
+ according to the function mapping f. *)
let add_substitute b f s =
let lim = String.length s in
let rec subst previous i =
diff --git a/stdlib/buffer.mli b/stdlib/buffer.mli
index 02451c51d..3cbf63ef8 100644
--- a/stdlib/buffer.mli
+++ b/stdlib/buffer.mli
@@ -64,14 +64,18 @@ val add_substring : t -> string -> int -> int -> unit
[ofs] in string [s] and appends them at the end of the buffer [b]. *)
val add_substitute : t -> (string -> string) -> string -> unit
-(** [add_substitute b f s] appends the string [s] at the end of the buffer [b]
- with substitution: variable names in [s] get replaced by their image by [f].
- A variable name is defined as a non empty sequence of alphanumeric or [_]
- characters (or alternatively an arbitrary sequence of characters
- enclosed by a pair of matching parentheses or curly brackets),
- that immediately follows a (non-escaped) [$] character;
- an escaped [$] character is a [$] that immediately follows
- a backslash character; it then stands for a plain [$].
+(** [add_substitute b f s] appends the string pattern [s] at the end
+ of the buffer [b] with substitution.
+ The substitution process looks for variables into
+ the pattern and substitutes each variable name by its value, as
+ obtained by applying the mapping [f] to the variable name. Inside the
+ string pattern, a variable name immediately follows a non-escaped
+ [$] character and is one of the following:
+ - a non empty sequence of alphanumeric or [_] characters,
+ - an arbitrary sequence of characters enclosed by a pair of
+ matching parentheses or curly brackets.
+ An escaped [$] character is a [$] that immediately folows a backslash
+ character; it then stands for a plain [$].
Raise [Not_found] if the closing character of a parenthesized variable
cannot be found. *)
diff --git a/stdlib/printf.mli b/stdlib/printf.mli
index cf1be6c0a..ce83977b2 100644
--- a/stdlib/printf.mli
+++ b/stdlib/printf.mli
@@ -65,19 +65,11 @@ val fprintf : out_channel -> ('a, out_channel, unit, unit) format -> 'a
[out_channel -> unit]) and apply it to [outchan].
- [$]: variable substitution in strings. Takes two arguments: a
function mapping from variable names to string values and a
- string pattern. After proper substitution, outputs the resulting
- string pattern. The substitution process looks for variables into
- the pattern and substitutes each variable name by its value, as
- obtained by applying the mapping to the variable name. Inside the
- string pattern, a variable name immediately follows a non-escaped
- [$] character and is one of the following:
- - a non empty sequence of alphanumeric or [_] characters,
- - an arbitrary sequence of characters enclosed by a pair of
- matching parentheses or curly brackets.
- An escaped [$] character is a [$] immediately preceded by a backslash
- character. Into the string pattern, an escaped [$] character is
- equivalent to any other [$] character that does not introduce a
- variable name: it stands for a plain [$] character.
+ string pattern where any identifier following a dollar sign is
+ considered a variable name. Each variable name is replaced by its
+ value as specified by the mapping, and the resulting string
+ pattern is inserted in the output. See {!Buffer.add_substitute} for
+ details on variable syntax.
- [!]: take no argument and flush the output.
- [%]: take no argument and output one [%] character.