Skip to content

Commit

Permalink
Port optimization about not updating start_p/curr_p to non-ml mode of…
Browse files Browse the repository at this point in the history
… ocamllex
  • Loading branch information
alainfrisch committed Jan 30, 2018
1 parent 1030265 commit 6877c43
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 8 deletions.
6 changes: 6 additions & 0 deletions Changes
Expand Up @@ -138,6 +138,12 @@ Working version
- GPR#1585: optimize output of "ocamllex -ml"
(Alain Frisch, review by Frédéric Bour and Gabriel Scherer)

- GPR#1590: ocamllex-generated lexers can be instructed not to update their
lex_curr_p/lex_start_p by setting lex_curr_p to Lexing.dummy_pos,
resuting in a significant performance gain when those fields are not
required
(Alain Frisch, review by ...)

### Manual and documentation:

- PR#7647, GPR#1384: emphasize ocaml.org website and forum in README
Expand Down
17 changes: 10 additions & 7 deletions stdlib/lexing.ml
Expand Up @@ -63,7 +63,7 @@ external c_new_engine : lex_tables -> int -> lexbuf -> int

let engine tbl state buf =
let result = c_engine tbl state buf in
if result >= 0 then begin
if result >= 0 && buf.lex_curr_p != dummy_pos then begin
buf.lex_start_p <- buf.lex_curr_p;
buf.lex_curr_p <- {buf.lex_curr_p
with pos_cnum = buf.lex_abs_pos + buf.lex_curr_pos};
Expand All @@ -73,7 +73,7 @@ let engine tbl state buf =

let new_engine tbl state buf =
let result = c_new_engine tbl state buf in
if result >= 0 then begin
if result >= 0 && buf.lex_curr_p != dummy_pos then begin
buf.lex_start_p <- buf.lex_curr_p;
buf.lex_curr_p <- {buf.lex_curr_p
with pos_cnum = buf.lex_abs_pos + buf.lex_curr_pos};
Expand Down Expand Up @@ -215,10 +215,12 @@ let lexeme_end_p lexbuf = lexbuf.lex_curr_p

let new_line lexbuf =
let lcp = lexbuf.lex_curr_p in
lexbuf.lex_curr_p <- { lcp with
pos_lnum = lcp.pos_lnum + 1;
pos_bol = lcp.pos_cnum;
}
if lcp != dummy_pos then
lexbuf.lex_curr_p <-
{ lcp with
pos_lnum = lcp.pos_lnum + 1;
pos_bol = lcp.pos_cnum;
}



Expand All @@ -227,5 +229,6 @@ let new_line lexbuf =
let flush_input lb =
lb.lex_curr_pos <- 0;
lb.lex_abs_pos <- 0;
lb.lex_curr_p <- {lb.lex_curr_p with pos_cnum = 0};
let lcp = lb.lex_curr_p in
if lcp != dummy_pos then lb.lex_curr_p <- {lcp with pos_cnum = 0};
lb.lex_buffer_len <- 0;
7 changes: 6 additions & 1 deletion stdlib/lexing.mli
Expand Up @@ -73,7 +73,12 @@ type lexbuf =
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]).
*)
Updating [lex_curr_p] and [lex_start_p] is disabled if
[lex_curr_p] is physically equal to [dummy_pos]. Setting
[lex_curr_p] to [dummy_pos] before calling the engine can thus be
used to avoid useless allocations and memory writes in contexts where
[lex_start_p] and [lex_curr_p] are not needed. *)

val from_channel : in_channel -> lexbuf
(** Create a lexer buffer on the given input channel.
Expand Down

0 comments on commit 6877c43

Please sign in to comment.