Răsfoiți Sursa

automate + simplify lexer line_index build

Nicolas Cannasse 14 ani în urmă
părinte
comite
c62bce5de9
11 a modificat fișierele cu 65 adăugiri și 71 ștergeri
  1. 1 3
      common.ml
  2. 1 1
      gencpp.ml
  3. 1 1
      genjs.ml
  4. 1 1
      genneko.ml
  5. 1 1
      genphp.ml
  6. 1 1
      genswf8.ml
  7. 1 1
      genswf9.ml
  8. 47 58
      lexer.mll
  9. 0 2
      main.ml
  10. 1 1
      parser.ml
  11. 10 1
      typer.ml

+ 1 - 3
common.ml

@@ -76,7 +76,6 @@ type context = {
 	mutable js_gen : (unit -> unit) option;
 	(* typing *)
 	mutable basic : basic_types;
-	mutable lines : Lexer.line_index;
 }
 
 exception Abort of string * Ast.pos
@@ -121,8 +120,7 @@ let create v =
 			tnull = (fun _ -> assert false);
 			tstring = m;
 			tarray = (fun _ -> assert false);
-		};
-		lines = Lexer.build_line_index();
+		};		
 	}
 
 let clone com =

+ 1 - 1
gencpp.ml

@@ -1161,7 +1161,7 @@ and gen_expression ctx retval expression =
 				find_local_functions_ctx ctx expression;
 				let want_value = (return_from_block && !remaining = 1) in
 				find_local_return_blocks_ctx ctx want_value expression;
-				let line = Lexer.find_line_index ctx.ctx_common.lines expression.epos in
+				let line = Lexer.get_error_line expression.epos in
 				output_i ("HX_SOURCE_POS(\"" ^ (Ast.s_escape expression.epos.pfile) ^ "\","
 					^ (string_of_int line) ^ ")\n" );
 				output_i "";

+ 1 - 1
genjs.ml

@@ -257,7 +257,7 @@ and gen_expr ctx e =
 		ctx.in_value <- false;
 		ctx.in_loop <- false;
 		if snd ctx.curmethod then
-			ctx.curmethod <- (fst ctx.curmethod ^ "@" ^ string_of_int (Lexer.find_line_index ctx.com.lines e.epos), true)
+			ctx.curmethod <- (fst ctx.curmethod ^ "@" ^ string_of_int (Lexer.get_error_line e.epos), true)
 		else
 			ctx.curmethod <- (fst ctx.curmethod, true);
 		print ctx "function(%s) " (String.concat "," (List.map ident (List.map arg_name f.tf_args)));

+ 1 - 1
genneko.ml

@@ -65,7 +65,7 @@ let pos ctx p =
 	) in
 	{
 		psource = file;
-		pline = Lexer.find_line_index ctx.com.lines p;
+		pline = Lexer.get_error_line p;
 	}
 
 let gen_global_name ctx path =

+ 1 - 1
genphp.ml

@@ -1190,7 +1190,7 @@ and gen_expr ctx e =
 		let old_meth = ctx.curmethod in
 		ctx.in_value <- None;
 		ctx.in_loop <- false;
-		ctx.curmethod <- ctx.curmethod ^ "@" ^ string_of_int (Lexer.find_line_index ctx.com.lines e.epos);
+		ctx.curmethod <- ctx.curmethod ^ "@" ^ string_of_int (Lexer.get_error_line e.epos);
 		gen_inline_function ctx f false e.epos;
 		ctx.curmethod <- old_meth;
 		ctx.in_value <- fst old;

+ 1 - 1
genswf8.ml

@@ -1021,7 +1021,7 @@ and gen_expr_2 ctx retval e =
 		let old_meth = ctx.curmethod in
 		let reg_super = Codegen.local_find true "super" f.tf_expr in
 		if snd ctx.curmethod then
-			ctx.curmethod <- (fst ctx.curmethod ^ "@" ^ string_of_int (Lexer.find_line_index ctx.com.lines e.epos), true)
+			ctx.curmethod <- (fst ctx.curmethod ^ "@" ^ string_of_int (Lexer.get_error_line e.epos), true)
 		else
 			ctx.curmethod <- (fst ctx.curmethod, true);
 		(* only keep None bindings, for protect *)

+ 1 - 1
genswf9.ml

@@ -532,7 +532,7 @@ let begin_switch ctx =
 
 let debug_infos ?(is_min=true) ctx p =
 	if ctx.com.debug then begin
-		let line = Lexer.find_line_index ctx.com.lines (if is_min then p else { p with pmin = p.pmax }) in
+		let line = Lexer.get_error_line (if is_min then p else { p with pmin = p.pmax }) in
 		if ctx.last_file <> p.pfile then begin
 			write ctx (HDebugFile (if ctx.debugger then try Common.get_full_path p.pfile with _ -> p.pfile else p.pfile));
 			ctx.last_file <- p.pfile;

+ 47 - 58
lexer.mll

@@ -40,14 +40,32 @@ let error_msg = function
 	| Invalid_escape -> "Invalid escape sequence"
 	| Invalid_option -> "Invalid regular expression option"
 
-let cur_file = ref ""
-let cur_line = ref 1
-let all_lines = Hashtbl.create 0
-let lines = ref []
+type lexer_file = {
+	lfile : string;
+	mutable lline : int;
+	mutable lmaxline : int;
+	mutable llines : (int * int) list;
+	mutable lrlines : (int * int) list;
+}
+
+let make_file file =
+	{
+		lfile = file;
+		lline = 1;
+		lmaxline = 1;
+		llines = [];
+		lrlines = [];		
+	}
+
+
+let cur = ref (make_file "")
+
+let all_files = Hashtbl.create 0
+
 let buf = Buffer.create 100
 
 let error e pos =
-	raise (Error (e,{ pmin = pos; pmax = pos; pfile = !cur_file }))
+	raise (Error (e,{ pmin = pos; pmax = pos; pfile = !cur.lfile }))
 
 let keywords =
 	let h = Hashtbl.create 3 in
@@ -61,47 +79,45 @@ let keywords =
 	h
 
 let init file =
-	cur_file := file;
-	cur_line := 1;
-	lines := []
-
-let save_lines() =
-	Hashtbl.replace all_lines !cur_file !lines
+	let f = make_file file in
+	cur := f;
+	Hashtbl.add all_files file f
 
 let save() =
-	save_lines();
-	!cur_file, !cur_line
+	!cur
 
-let restore (file,line) =
-	save_lines();
-	cur_file := file;
-	cur_line := line;
-	lines := Hashtbl.find all_lines file
+let restore c =	
+	cur := c
 
 let newline lexbuf =
-	lines :=  (lexeme_end lexbuf,!cur_line) :: !lines;
-	incr cur_line
+	let cur = !cur in
+	cur.llines <- (lexeme_end lexbuf,cur.lline) :: cur.llines;	
+	cur.lline <- cur.lline + 1
 
-let find_line p lines =
-	let rec loop line delta = function
-		| [] -> line + 1, p - delta
+let find_line p f =
+	let rec loop delta = function
+		| [] -> f.lmaxline, p - delta
 		| (lp,line) :: l when lp > p -> line, p - delta
-		| (lp,line) :: l -> loop line lp l
+		| (lp,_) :: l -> loop lp l
 	in
-	loop 0 0 lines
+	if f.lmaxline <> f.lline then begin
+		f.lmaxline <- f.lline;
+		f.lrlines <- List.rev f.llines;
+	end;
+	loop 0 f.lrlines
 
 let get_error_line p =
-	let lines = List.rev (try Hashtbl.find all_lines p.pfile with Not_found -> []) in
-	let l, _ = find_line p.pmin lines in
+	let file = (try Hashtbl.find all_files p.pfile with Not_found -> make_file p.pfile) in
+	let l, _ = find_line p.pmin file in
 	l
 
 let get_error_pos printer p =
 	if p.pmin = -1 then
 		"(unknown)"
 	else
-		let lines = List.rev (try Hashtbl.find all_lines p.pfile with Not_found -> []) in
-		let l1, p1 = find_line p.pmin lines in
-		let l2, p2 = find_line p.pmax lines in
+		let file = (try Hashtbl.find all_files p.pfile with Not_found -> make_file p.pfile) in
+		let l1, p1 = find_line p.pmin file in
+		let l2, p2 = find_line p.pmax file in
 		if l1 = l2 then begin
 			let s = (if p1 = p2 then Printf.sprintf " %d" p1 else Printf.sprintf "s %d-%d" p1 p2) in
 			Printf.sprintf "%s character%s" (printer p.pfile l1) s
@@ -114,7 +130,7 @@ let store lexbuf = Buffer.add_string buf (lexeme lexbuf)
 let add c = Buffer.add_string buf c
 
 let mk_tok t pmin pmax =
-	t , { pfile = !cur_file; pmin = pmin; pmax = pmax }
+	t , { pfile = !cur.lfile; pmin = pmin; pmax = pmax }
 
 let mk lexbuf t =
 	mk_tok t (lexeme_start lexbuf) (lexeme_end lexbuf)
@@ -127,33 +143,6 @@ let mk_ident lexbuf =
 let invalid_char lexbuf =
 	error (Invalid_character (lexeme_char lexbuf 0)) (lexeme_start lexbuf)
 
-type file_index = {
-	f_file : string;
-	f_lines : (int * int) list;
-	f_max_line : int;
-}
-
-type line_index = (string, file_index) PMap.t
-
-let make_index f lines =
-	{
-		f_file = f;
-		f_lines = List.rev lines;
-		f_max_line = (match lines with (_,line) :: _ -> line + 1 | [] -> 1);
-	}
-
-let build_line_index() =
-	Hashtbl.fold (fun f l acc -> PMap.add f (make_index f l) acc) all_lines PMap.empty
-
-let find_line_index idx p =
-	let idx = (try PMap.find p.pfile idx with Not_found -> make_index p.pfile []) in
-	let ppos = p.pmin in
-	let rec loop = function
-		| [] -> idx.f_max_line
-		| (lp,line) :: l -> if lp > ppos then line else loop l
-	in
-	loop idx.f_lines
-
 }
 
 let ident = ('_'* ['a'-'z'] ['_' 'a'-'z' 'A'-'Z' '0'-'9']* | '_'+ | '_'+ ['0'-'9'] ['_' 'a'-'z' 'A'-'Z' '0'-'9']* )

+ 0 - 2
main.ml

@@ -256,7 +256,6 @@ try
 		has_error := true;
 	);
 	Parser.display_error := (fun e p ->
-		Lexer.save_lines();
 		com.error (Parser.error_msg e) p;
 	);
 	Parser.use_doc := false;
@@ -580,7 +579,6 @@ try
 		com.main <- main;
 		com.types <- types;
 		com.modules <- modules;
-		com.lines <- Lexer.build_line_index();
 		if com.platform = Flash9 then Common.add_filter com (fun() -> List.iter Codegen.fix_overrides com.types);
 		let filters = [
 			if com.foptimize then Optimizer.reduce_expression ctx else Optimizer.sanitize ctx;

+ 1 - 1
parser.ml

@@ -754,7 +754,7 @@ let parse ctx code =
 				| (Const (Int s),_) -> int_of_string s
 				| (t,p) -> error (Unexpected t) p
 			) in
-			Lexer.cur_line := line - 1;
+			!(Lexer.cur).Lexer.lline <- line - 1;
 			next_token();
 		| _ ->
 			tk

+ 10 - 1
typer.ml

@@ -1866,15 +1866,24 @@ let get_type_patch ctx t sub =
 
 let parse_string ctx s p =
 	let old = Lexer.save() in
+	let old_file = (try Some (Hashtbl.find Lexer.all_files p.pfile) with Not_found -> None) in
+	let restore() =
+		(match old_file with
+		| None -> ()
+		| Some f -> Hashtbl.replace Lexer.all_files p.pfile f);
+		Lexer.restore old;
+	in
 	Lexer.init p.pfile;
 	let _, decls = try
 		Parser.parse ctx.com (Lexing.from_string s)
 	with Parser.Error (e,_) ->
+		restore();
 		failwith (Parser.error_msg e)
 	| Lexer.Error (e,_) ->
+		restore();
 		failwith (Lexer.error_msg e)
 	in
-	Lexer.restore old;
+	restore();
 	match decls with
 	| [(d,_)] -> d
 	| _ -> assert false