summaryrefslogtreecommitdiffstats
path: root/stdlib/lexing.mli
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2008-10-08 13:09:39 +0000
committerDamien Doligez <damien.doligez-inria.fr>2008-10-08 13:09:39 +0000
commit2b0441401a9686529cfe8d97cf73ecc09a51bef5 (patch)
tree1e1bf18bb6810b34696e0e4329a60c3f6c1bcabb /stdlib/lexing.mli
parent29e590ccb9fe1a9330a6809a972a0e84e80653f7 (diff)
merge changes between 3.10.2 and the end of branch 3.10
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9079 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/lexing.mli')
-rw-r--r--stdlib/lexing.mli7
1 files changed, 4 insertions, 3 deletions
diff --git a/stdlib/lexing.mli b/stdlib/lexing.mli
index 1868825ce..884bf3844 100644
--- a/stdlib/lexing.mli
+++ b/stdlib/lexing.mli
@@ -62,10 +62,11 @@ type lexbuf =
The lexer buffer holds the current state of the scanner, plus
a function to refill the buffer from the input.
- Note that the lexing engine will only change the [pos_cnum] field
+ At each token, the lexing engine will copy [lex_curr_p] to
+ [lex_start_p], then change the [pos_cnum] field
of [lex_curr_p] by updating it with the number of characters read
- since the start of the [lexbuf]. The other fields are copied
- without change by the lexing engine. In order to keep them
+ since the start of the [lexbuf]. The other fields are left
+ unchanged by the lexing engine. In order to keep them
accurate, they must be initialised before the first use of the
lexbuf, and updated by the relevant lexer actions (i.e. at each
end of line -- see also [new_line]).