summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Makefile12
-rw-r--r--bytecomp/matching.ml8
-rw-r--r--bytecomp/translcore.ml9
-rw-r--r--bytecomp/translmod.ml8
-rw-r--r--debugger/pos.ml23
-rw-r--r--debugger/source.ml15
-rwxr-xr-xexperimental/doligez/checkheaders2
-rw-r--r--ocamldoc/Makefile1
-rw-r--r--ocamldoc/ocamldoc.hva11
-rw-r--r--otherlibs/dynlink/Makefile2
-rw-r--r--otherlibs/labltk/browser/Makefile.shared4
-rw-r--r--otherlibs/labltk/browser/help.ml168
-rw-r--r--otherlibs/labltk/browser/help.txt2
-rw-r--r--parsing/linenum.mli23
-rw-r--r--parsing/linenum.mll74
-rw-r--r--parsing/location.ml24
-rw-r--r--parsing/parse.ml6
-rw-r--r--parsing/printast.ml4
-rw-r--r--parsing/syntaxerr.ml4
-rw-r--r--testsuite/tests/tool-ocamldoc/.ignore1
-rw-r--r--tools/Makefile.shared8
-rw-r--r--toplevel/opttoploop.ml3
-rw-r--r--toplevel/toploop.ml3
23 files changed, 48 insertions, 367 deletions
diff --git a/Makefile b/Makefile
index f133c1720..46291acc9 100644
--- a/Makefile
+++ b/Makefile
@@ -40,7 +40,7 @@ UTILS=utils/misc.cmo utils/tbl.cmo utils/config.cmo \
OPTUTILS=$(UTILS)
-PARSING=parsing/linenum.cmo parsing/location.cmo parsing/longident.cmo \
+PARSING=parsing/location.cmo parsing/longident.cmo \
parsing/syntaxerr.cmo parsing/parser.cmo \
parsing/lexer.cmo parsing/parse.cmo parsing/printast.cmo
@@ -423,16 +423,6 @@ partialclean::
beforedepend:: parsing/lexer.ml
-# The auxiliary lexer for counting line numbers
-
-parsing/linenum.ml: parsing/linenum.mll
- $(CAMLLEX) parsing/linenum.mll
-
-partialclean::
- rm -f parsing/linenum.ml
-
-beforedepend:: parsing/linenum.ml
-
# The bytecode compiler compiled with the native-code compiler
ocamlc.opt: $(COMPOBJS:.cmo=.cmx)
diff --git a/bytecomp/matching.ml b/bytecomp/matching.ml
index 402ac12ad..a464590e4 100644
--- a/bytecomp/matching.ml
+++ b/bytecomp/matching.ml
@@ -2542,13 +2542,7 @@ let compile_matching loc repr handler_fun arg pat_act_list partial =
let partial_function loc () =
(* [Location.get_pos_info] is too expensive *)
- let fname = match loc.Location.loc_start.Lexing.pos_fname with
- | "" -> !Location.input_name
- | x -> x
- in
- let pos = loc.Location.loc_start in
- let line = pos.Lexing.pos_lnum in
- let char = pos.Lexing.pos_cnum - pos.Lexing.pos_bol in
+ let (fname, line, char) = Location.get_pos_info loc.Location.loc_start in
Lprim(Praise, [Lprim(Pmakeblock(0, Immutable),
[transl_path Predef.path_match_failure;
Lconst(Const_block(0,
diff --git a/bytecomp/translcore.ml b/bytecomp/translcore.ml
index 1e68756cd..d784e51ee 100644
--- a/bytecomp/translcore.ml
+++ b/bytecomp/translcore.ml
@@ -531,14 +531,7 @@ let primitive_is_ccall = function
(* Assertions *)
let assert_failed loc =
- (* [Location.get_pos_info] is too expensive *)
- let fname = match loc.Location.loc_start.Lexing.pos_fname with
- | "" -> !Location.input_name
- | x -> x
- in
- let pos = loc.Location.loc_start in
- let line = pos.Lexing.pos_lnum in
- let char = pos.Lexing.pos_cnum - pos.Lexing.pos_bol in
+ let (fname, line, char) = Location.get_pos_info loc.Location.loc_start in
Lprim(Praise, [Lprim(Pmakeblock(0, Immutable),
[transl_path Predef.path_assert_failure;
Lconst(Const_block(0,
diff --git a/bytecomp/translmod.ml b/bytecomp/translmod.ml
index 7f52f99a1..a80fee68f 100644
--- a/bytecomp/translmod.ml
+++ b/bytecomp/translmod.ml
@@ -109,13 +109,7 @@ let mod_prim name =
fatal_error ("Primitive " ^ name ^ " not found.")
let undefined_location loc =
- (* Confer Translcore.assert_failed *)
- let fname = match loc.Location.loc_start.Lexing.pos_fname with
- | "" -> !Location.input_name
- | x -> x in
- let pos = loc.Location.loc_start in
- let line = pos.Lexing.pos_lnum in
- let char = pos.Lexing.pos_cnum - pos.Lexing.pos_bol in
+ let (fname, line, char) = Location.get_pos_info loc.Location.loc_start in
Lconst(Const_block(0,
[Const_base(Const_string fname);
Const_base(Const_int line);
diff --git a/debugger/pos.ml b/debugger/pos.ml
index 6c43f4339..995168648 100644
--- a/debugger/pos.ml
+++ b/debugger/pos.ml
@@ -20,23 +20,8 @@ open Source;;
let get_desc ev =
let loc = ev.ev_loc in
- if loc.loc_start.pos_fname <> ""
- then Printf.sprintf "file %s, line %d, characters %d-%d"
- loc.loc_start.pos_fname loc.loc_start.pos_lnum
- (loc.loc_start.pos_cnum - loc.loc_start.pos_bol + 1)
- (loc.loc_end.pos_cnum - loc.loc_start.pos_bol + 1)
- else begin
- let filename = source_of_module ev.ev_loc.loc_start ev.ev_module in
- try
- let (start, line) = line_of_pos (get_buffer loc.loc_start ev.ev_module)
- loc.loc_start.pos_cnum
- in
- Printf.sprintf "file %s, line %d, characters %d-%d"
- filename line (loc.loc_start.pos_cnum - start + 1)
- (loc.loc_end.pos_cnum - start + 1)
- with Not_found | Out_of_range ->
- Printf.sprintf "file %s, characters %d-%d"
- filename (loc.loc_start.pos_cnum + 1)
- (loc.loc_end.pos_cnum + 1)
- end
+ Printf.sprintf "file %s, line %d, characters %d-%d"
+ loc.loc_start.pos_fname loc.loc_start.pos_lnum
+ (loc.loc_start.pos_cnum - loc.loc_start.pos_bol + 1)
+ (loc.loc_end.pos_cnum - loc.loc_start.pos_bol + 1)
;;
diff --git a/debugger/source.ml b/debugger/source.ml
index 0314cfacb..372b8be37 100644
--- a/debugger/source.ml
+++ b/debugger/source.ml
@@ -39,20 +39,7 @@ let source_of_module pos mdle =
Debugger_config.load_path_for
!Config.load_path in
let fname = pos.Lexing.pos_fname in
- if fname = "" then
- let innermost_module =
- try
- let dot_index = String.rindex mdle '.' in
- String.sub mdle (succ dot_index) (pred ((String.length mdle) - dot_index))
- with Not_found -> mdle in
- let rec loop =
- function
- | [] -> raise Not_found
- | ext :: exts ->
- try find_in_path_uncap path (innermost_module ^ ext)
- with Not_found -> loop exts
- in loop source_extensions
- else if Filename.is_implicit fname then
+ if Filename.is_implicit fname then
find_in_path path fname
else
fname
diff --git a/experimental/doligez/checkheaders b/experimental/doligez/checkheaders
index 671325a5e..044080f2e 100755
--- a/experimental/doligez/checkheaders
+++ b/experimental/doligez/checkheaders
@@ -106,6 +106,8 @@ FNR == 1 {
add_exception("./ocamldoc/Changes.txt");
add_exception("./ocamldoc/ocamldoc.sty"); # public domain
add_exception("./otherlibs/labltk/browser/help.txt");
+ add_exception("./otherlibs/labltk/camltk/modules"); # generated
+ add_exception("./otherlibs/labltk/labltk/modules"); # generated
add_exception("./tools/objinfo_helper.c"); # non-INRIA
add_exception("./tools/magic"); # public domain ?
add_exception("./Upgrading");
diff --git a/ocamldoc/Makefile b/ocamldoc/Makefile
index 0c4f61ecf..d04809aa3 100644
--- a/ocamldoc/Makefile
+++ b/ocamldoc/Makefile
@@ -146,7 +146,6 @@ OCAMLCMOFILES=$(OCAMLSRCDIR)/parsing/printast.cmo \
$(OCAMLSRCDIR)/utils/warnings.cmo \
$(OCAMLSRCDIR)/utils/ccomp.cmo \
$(OCAMLSRCDIR)/utils/consistbl.cmo \
- $(OCAMLSRCDIR)/parsing/linenum.cmo\
$(OCAMLSRCDIR)/parsing/location.cmo\
$(OCAMLSRCDIR)/parsing/longident.cmo \
$(OCAMLSRCDIR)/parsing/syntaxerr.cmo \
diff --git a/ocamldoc/ocamldoc.hva b/ocamldoc/ocamldoc.hva
index 454cee9e7..1d0eb60d4 100644
--- a/ocamldoc/ocamldoc.hva
+++ b/ocamldoc/ocamldoc.hva
@@ -1,3 +1,14 @@
+%(***********************************************************************)
+%(* OCamldoc *)
+%(* *)
+%(* Maxence Guesdon, projet Cristal, INRIA Rocquencourt *)
+%(* *)
+%(* Copyright 2001 Institut National de Recherche en Informatique et *)
+%(* en Automatique. All rights reserved. This file is distributed *)
+%(* under the terms of the Q Public License version 1.0. *)
+%(* *)
+%(***********************************************************************)
+
\usepackage{alltt}
\newenvironment{ocamldoccode}{\begin{alltt}}{\end{alltt}}
\newenvironment{ocamldocdescription}{\begin{quote}}{\end{quote}}
diff --git a/otherlibs/dynlink/Makefile b/otherlibs/dynlink/Makefile
index c44451c0e..e6a632956 100644
--- a/otherlibs/dynlink/Makefile
+++ b/otherlibs/dynlink/Makefile
@@ -28,7 +28,7 @@ COMPILEROBJS=\
../../utils/misc.cmo ../../utils/config.cmo ../../utils/clflags.cmo \
../../utils/tbl.cmo ../../utils/consistbl.cmo \
../../utils/terminfo.cmo ../../utils/warnings.cmo \
- ../../parsing/asttypes.cmi ../../parsing/linenum.cmo \
+ ../../parsing/asttypes.cmi \
../../parsing/location.cmo ../../parsing/longident.cmo \
../../typing/ident.cmo ../../typing/path.cmo \
../../typing/primitive.cmo ../../typing/types.cmo \
diff --git a/otherlibs/labltk/browser/Makefile.shared b/otherlibs/labltk/browser/Makefile.shared
index b6be2fc33..35b8edf7f 100644
--- a/otherlibs/labltk/browser/Makefile.shared
+++ b/otherlibs/labltk/browser/Makefile.shared
@@ -23,7 +23,7 @@ OBJ = list2.cmo useunix.cmo setpath.cmo lexical.cmo \
help.cmo \
viewer.cmo typecheck.cmo editor.cmo main.cmo
-JG = jg_tk.cmo jg_config.cmo jg_bind.cmo jg_completion.cmo \
+JG = jg_tk.cmo jg_config.cmo jg_bind.cmo jg_completion.cmo \
jg_box.cmo \
jg_button.cmo jg_toplevel.cmo jg_text.cmo jg_message.cmo \
jg_menu.cmo jg_entry.cmo jg_multibox.cmo jg_memo.cmo
@@ -68,7 +68,7 @@ install:
clean:
rm -f *.cm? ocamlbrowser$(EXE) dummy.mli *~ *.orig *.$(O) help.ml
-depend:
+depend: help.ml
$(CAMLDEP) *.ml *.mli > .depend
shell.cmo: dummy.cmi
diff --git a/otherlibs/labltk/browser/help.ml b/otherlibs/labltk/browser/help.ml
deleted file mode 100644
index 632e762fd..000000000
--- a/otherlibs/labltk/browser/help.ml
+++ /dev/null
@@ -1,168 +0,0 @@
-let text = "\
-\032 OCamlBrowser Help\n\
-\n\
-USE\n\
-\n\
-\032 OCamlBrowser is composed of three tools, the Editor, which allows\n\
-\032 one to edit/typecheck/analyse .mli and .ml files, the Viewer, to\n\
-\032 walk around compiled modules, and the Shell, to run an OCaml\n\
-\032 subshell. You may only have one instance of Editor and Viewer, but\n\
-\032 you may use several subshells.\n\
-\n\
-\032 As with the compiler, you may specify a different path for the\n\
-\032 standard library by setting OCAMLLIB. You may also extend the\n\
-\032 initial load path (only standard library by default) by using the\n\
-\032 -I command line option. The -nolabels, -rectypes and -w options are\n\
-\032 also accepted, and inherited by subshells.\n\
-\032 The -oldui options selects the old multi-window interface. The\n\
-\032 default is now more like Smalltalk's class browser.\n\
-\n\
-1) Viewer\n\
-\n\
-\032 This is the first window you get when you start OCamlBrowser. It\n\
-\032 displays a search window, and the list of modules in the load path.\n\
-\032 At the top a row of menus.\n\
-\n\
-\032 File - Open and File - Editor give access to the editor.\n\
-\n\
-\032 File - Shell opens an OCaml shell.\n\
-\n\
-\032 View - Show all defs displays the signature of the currently\n\
-\032 selected module.\n\
-\n\
-\032 View - Search entry shows/hides the search entry just\n\
-\032 below the menu bar.\n\
-\n\
-\032 Modules - Path editor changes the load path.\n\
-\032 Pressing [Add to path] or Insert key adds selected directories\n\
-\032 to the load path.\n\
-\032 Pressing [Remove from path] or Delete key removes selected\n\
-\032 paths from the load path.\n\
-\n\
-\032 Modules - Reset cache rescans the load path and resets the module\n\
-\032 cache. Do it if you recompile some interface, or change the load\n\
-\032 path in a conflictual way.\n\
-\n\
-\032 Modules - Search symbol allows to search a symbol either by its\n\
-\032 name, like the bottom line of the viewer, or, more interestingly,\n\
-\032 by its type. Exact type searches for a type with exactly the same\n\
-\032 information as the pattern (variables match only variables),\n\
-\032 included type allows to give only partial information: the actual\n\
-\032 type may take more arguments and return more results, and variables\n\
-\032 in the pattern match anything. In both cases, argument and tuple\n\
-\032 order is irrelevant (*), and unlabeled arguments in the pattern\n\
-\032 match any label.\n\
-\n\
-\032 (*) To avoid combinatorial explosion of the search space, optional\n\
-\032 arguments in the actual type are ignored if (1) there are to many\n\
-\032 of them, and (2) they do not appear explicitly in the pattern.\n\
-\n\
-\032 The Search entry just below the menu bar allows one to search for\n\
-\032 an identifier in all modules, either by its name (? and * patterns\n\
-\032 allowed) or by its type (if there is an arrow in the input). When\n\
-\032 search by type is used, it is done in inclusion mode (cf. Modules -\n\
-\032 search symbol)\n\
-\n\
-\032 The Close all button is there to dismiss the windows created\n\
-\032 by the Detach button. By double-clicking on it you will quit the\n\
-\032 browser.\n\
-\n\
-\n\
-2) Module browsing\n\
-\n\
-\032 You select a module in the leftmost box by either cliking on it or\n\
-\032 pressing return when it is selected. Fast access is available in\n\
-\032 all boxes pressing the first few letter of the desired name.\n\
-\032 Double-clicking / double-return displays the whole signature for\n\
-\032 the module.\n\
-\n\
-\032 Defined identifiers inside the module are displayed in a box to the\n\
-\032 right of the previous one. If you click on one, this will either\n\
-\032 display its contents in another box (if this is a sub-module) or\n\
-\032 display the signature for this identifier below.\n\
-\n\
-\032 Signatures are clickable. Double clicking with the left mouse\n\
-\032 button on an identifier in a signature brings you to its signature,\n\
-\032 inside its module box.\n\
-\032 A single click on the right button pops up a menu displaying the\n\
-\032 type declaration for the selected identifier. Its title, when\n\
-\032 selectable, also brings you to its signature.\n\
-\n\
-\032 At the bottom, a series of buttons, depending on the context.\n\
-\032 * Detach copies the currently displayed signature in a new window,\n\
-\032 to keep it.\n\
-\032 * Impl and Intf bring you to the implementation or interface of\n\
-\032 the currently displayed signature, if it is available.\n\
-\n\
-\032 C-s opens a text search dialog for the displayed signature.\n\
-\n\
-3) File editor\n\
-\n\
-\032 You can edit files with it, but there is no auto-save nor undo at\n\
-\032 the moment. Otherwise you can use it as a browser, making\n\
-\032 occasional corrections.\n\
-\n\
-\032 The Edit menu contains commands for jump (C-g), search (C-s), and\n\
-\032 sending the current selection to a sub-shell (M-x). For this last\n\
-\032 option, you may choose the shell via a dialog.\n\
-\n\
-\032 Essential function are in the Compiler menu.\n\
-\n\
-\032 Preferences opens a dialog to set internals of the editor and\n\
-\032 type checker.\n\
-\n\
-\032 Lex (M-l) adds colors according to lexical categories.\n\
-\n\
-\032 Typecheck (M-t) verifies typing, and memorizes it to let one see an\n\
-\032 expression's type by double-clicking on it. This is also valid for\n\
-\032 interfaces. If an error occurs, the part of the interface preceding\n\
-\032 the error is computed.\n\
-\n\
-\032 After typechecking, pressing the right button pops up a menu giving\n\
-\032 the type of the pointed expression, and eventually allowing to\n\
-\032 follow some links.\n\
-\n\
-\032 Clear errors dismisses type checker error messages and warnings.\n\
-\n\
-\032 Signature shows the signature of the current file.\n\
-\n\
-4) Shell\n\
-\n\
-\032 When you create a shell, a dialog is presented to you, letting you\n\
-\032 choose which command you want to run, and the title of the shell\n\
-\032 (to choose it in the Editor).\n\
-\n\
-\032 You may change the default command by setting the OLABL environment\n\
-\032 variable.\n\
-\n\
-\032 The executed subshell is given the current load path.\n\
-\032 File: use a source file or load a bytecode file.\n\
-\032 You may also import the browser's path into the subprocess.\n\
-\032 History: M-p and M-n browse up and down.\n\
-\032 Signal: C-c interrupts and you can kill the subprocess.\n\
-\n\
-BUGS\n\
-\n\
-* When you quit the editor and some file was modified, a dialogue is\n\
-\032 displayed asking wether you want to really quit or not. But 1) if\n\
-\032 you quit directly from the viewer, there is no dialogue at all, and\n\
-\032 2) if you close from the window manager, the dialogue is displayed,\n\
-\032 but you cannot cancel the destruction... Beware.\n\
-\n\
-* When you run it through xon, the shell hangs at the first error. But\n\
-\032 its ok if you start ocamlbrowser from a remote shell...\n\
-\n\
-TODO\n\
-\n\
-* Complete cross-references.\n\
-\n\
-* Power up editor.\n\
-\n\
-* Add support for the debugger.\n\
-\n\
-* Make this a real programming environment, both for beginners an\n\
-\032 experimented users.\n\
-\n\
-\n\
-Bug reports and comments to <garrigue@kurims.kyoto-u.ac.jp>\n\
-";;
diff --git a/otherlibs/labltk/browser/help.txt b/otherlibs/labltk/browser/help.txt
index 62bfc5921..3b8c9b865 100644
--- a/otherlibs/labltk/browser/help.txt
+++ b/otherlibs/labltk/browser/help.txt
@@ -159,7 +159,7 @@ TODO
* Add support for the debugger.
-* Make this a real programming environment, both for beginners an
+* Make this a real programming environment, both for beginners and
experimented users.
diff --git a/parsing/linenum.mli b/parsing/linenum.mli
deleted file mode 100644
index e63694761..000000000
--- a/parsing/linenum.mli
+++ /dev/null
@@ -1,23 +0,0 @@
-(***********************************************************************)
-(* *)
-(* OCaml *)
-(* *)
-(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
-(* *)
-(* Copyright 1997 Institut National de Recherche en Informatique et *)
-(* en Automatique. All rights reserved. This file is distributed *)
-(* under the terms of the Q Public License version 1.0. *)
-(* *)
-(***********************************************************************)
-
-(* $Id$ *)
-
-(* An auxiliary lexer for determining the line number corresponding to
- a file position, honoring the directives # linenum "filename" *)
-
-val for_position: string -> int -> string * int * int
- (* [Linenum.for_position file loc] returns a triple describing
- the location [loc] in the file named [file].
- First result is name of actual source file.
- Second result is line number in that source file.
- Third result is position of beginning of that line in [file]. *)
diff --git a/parsing/linenum.mll b/parsing/linenum.mll
deleted file mode 100644
index 1844d361f..000000000
--- a/parsing/linenum.mll
+++ /dev/null
@@ -1,74 +0,0 @@
-(***********************************************************************)
-(* *)
-(* OCaml *)
-(* *)
-(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
-(* *)
-(* Copyright 1997 Institut National de Recherche en Informatique et *)
-(* en Automatique. All rights reserved. This file is distributed *)
-(* under the terms of the Q Public License version 1.0. *)
-(* *)
-(***********************************************************************)
-
-(* $Id$ *)
-
-(* An auxiliary lexer for determining the line number corresponding to
- a file position, honoring the directives # linenum "filename" *)
-
-{
-let filename = ref ""
-let linenum = ref 0
-let linebeg = ref 0
-
-let parse_sharp_line s =
- try
- (* Update the line number and file name *)
- let l1 = ref 0 in
- while let c = s.[!l1] in c < '0' || c > '9' do incr l1 done;
- let l2 = ref (!l1 + 1) in
- while let c = s.[!l2] in c >= '0' && c <= '9' do incr l2 done;
- linenum := int_of_string(String.sub s !l1 (!l2 - !l1));
- let f1 = ref (!l2 + 1) in
- while !f1 < String.length s && s.[!f1] <> '"' do incr f1 done;
- let f2 = ref (!f1 + 1) in
- while !f2 < String.length s && s.[!f2] <> '"' do incr f2 done;
- if !f1 < String.length s then
- filename := String.sub s (!f1 + 1) (!f2 - !f1 - 1)
- with Failure _ | Invalid_argument _ ->
- Misc.fatal_error "Linenum.parse_sharp_line"
-}
-
-rule skip_line = parse
- "#" [' ' '\t']* ['0'-'9']+ [' ' '\t']*
- ("\"" [^ '\n' '\r' '"' (* '"' *) ] * "\"")?
- [^ '\n' '\r'] *
- ('\n' | '\r' | "\r\n")
- { parse_sharp_line(Lexing.lexeme lexbuf);
- linebeg := Lexing.lexeme_start lexbuf;
- Lexing.lexeme_end lexbuf }
- | [^ '\n' '\r'] *
- ('\n' | '\r' | "\r\n")
- { incr linenum;
- linebeg := Lexing.lexeme_start lexbuf;
- Lexing.lexeme_end lexbuf }
- | [^ '\n' '\r'] * eof
- { incr linenum;
- linebeg := Lexing.lexeme_start lexbuf;
- raise End_of_file }
-
-{
-
-let for_position file loc =
- let ic = open_in_bin file in
- let lb = Lexing.from_channel ic in
- filename := file;
- linenum := 1;
- linebeg := 0;
- begin try
- while skip_line lb <= loc do () done
- with End_of_file -> ()
- end;
- close_in ic;
- (!filename, !linenum - 1, !linebeg)
-
-}
diff --git a/parsing/location.ml b/parsing/location.ml
index e9a988245..e4c09aa3a 100644
--- a/parsing/location.ml
+++ b/parsing/location.ml
@@ -16,8 +16,6 @@ open Lexing
type t = { loc_start: position; loc_end: position; loc_ghost: bool };;
-let none = { loc_start = dummy_pos; loc_end = dummy_pos; loc_ghost = true };;
-
let in_file name =
let loc = {
pos_fname = name;
@@ -28,6 +26,8 @@ let in_file name =
{ loc_start = loc; loc_end = loc; loc_ghost = true }
;;
+let none = in_file "_none_";;
+
let curr lexbuf = {
loc_start = lexbuf.lex_start_p;
loc_end = lexbuf.lex_curr_p;
@@ -204,31 +204,21 @@ let (msg_file, msg_line, msg_chars, msg_to, msg_colon, msg_head) =
(* return file, line, char from the given position *)
let get_pos_info pos =
- let (filename, linenum, linebeg) =
- if pos.pos_fname = "" && !input_name = "" then
- ("", -1, 0)
- else if pos.pos_fname = "" then
- Linenum.for_position !input_name pos.pos_cnum
- else
- (pos.pos_fname, pos.pos_lnum, pos.pos_bol)
- in
- (filename, linenum, pos.pos_cnum - linebeg)
+ (pos.pos_fname, pos.pos_lnum, pos.pos_cnum - pos.pos_bol)
;;
let print ppf loc =
let (file, line, startchar) = get_pos_info loc.loc_start in
let endchar = loc.loc_end.pos_cnum - loc.loc_start.pos_cnum + startchar in
- let (startchar, endchar) =
- if startchar < 0 then (0, 1) else (startchar, endchar)
- in
- if file = "" then begin
+ if file = "//toplevel//" then begin
if highlight_locations ppf loc none then () else
fprintf ppf "Characters %i-%i:@."
loc.loc_start.pos_cnum loc.loc_end.pos_cnum
end else begin
fprintf ppf "%s%s%s%i" msg_file file msg_line line;
- fprintf ppf "%s%i" msg_chars startchar;
- fprintf ppf "%s%i%s@.%s" msg_to endchar msg_colon msg_head;
+ if startchar >= 0 then
+ fprintf ppf "%s%i%s%i" msg_chars startchar msg_to endchar;
+ fprintf ppf "%s@.%s" msg_colon msg_head;
end
;;
diff --git a/parsing/parse.ml b/parsing/parse.ml
index edeed48f2..cf862af3f 100644
--- a/parsing/parse.ml
+++ b/parsing/parse.ml
@@ -46,14 +46,14 @@ let wrap parsing_fun lexbuf =
| Lexer.Error(Lexer.Unterminated_string, _) as err -> raise err
| Lexer.Error(Lexer.Unterminated_string_in_comment, _) as err -> raise err
| Lexer.Error(Lexer.Illegal_character _, _) as err ->
- if !Location.input_name = "" then skip_phrase lexbuf;
+ if !Location.input_name = "//toplevel//" then skip_phrase lexbuf;
raise err
| Syntaxerr.Error _ as err ->
- if !Location.input_name = "" then maybe_skip_phrase lexbuf;
+ if !Location.input_name = "//toplevel//" then maybe_skip_phrase lexbuf;
raise err
| Parsing.Parse_error | Syntaxerr.Escape_error ->
let loc = Location.curr lexbuf in
- if !Location.input_name = ""
+ if !Location.input_name = "//toplevel//"
then maybe_skip_phrase lexbuf;
raise(Syntaxerr.Error(Syntaxerr.Other loc))
;;
diff --git a/parsing/printast.ml b/parsing/printast.ml
index ef49e0308..713295f6f 100644
--- a/parsing/printast.ml
+++ b/parsing/printast.ml
@@ -19,9 +19,7 @@ open Location;;
open Parsetree;;
let fmt_position f l =
- if l.pos_fname = "" && l.pos_lnum = 1
- then fprintf f "%d" l.pos_cnum
- else if l.pos_lnum = -1
+ if l.pos_lnum = -1
then fprintf f "%s[%d]" l.pos_fname l.pos_cnum
else fprintf f "%s[%d,%d+%d]" l.pos_fname l.pos_lnum l.pos_bol
(l.pos_cnum - l.pos_bol)
diff --git a/parsing/syntaxerr.ml b/parsing/syntaxerr.ml
index 00e06bba0..b0fda3695 100644
--- a/parsing/syntaxerr.ml
+++ b/parsing/syntaxerr.ml
@@ -26,8 +26,8 @@ exception Escape_error
let report_error ppf = function
| Unclosed(opening_loc, opening, closing_loc, closing) ->
- if String.length !Location.input_name = 0
- && Location.highlight_locations ppf opening_loc closing_loc
+ if !Location.input_name = "//toplevel//"
+ && Location.highlight_locations ppf opening_loc closing_loc
then fprintf ppf "Syntax error: '%s' expected, \
the highlighted '%s' might be unmatched" closing opening
else begin
diff --git a/testsuite/tests/tool-ocamldoc/.ignore b/testsuite/tests/tool-ocamldoc/.ignore
index 9832f01ce..866d4be88 100644
--- a/testsuite/tests/tool-ocamldoc/.ignore
+++ b/testsuite/tests/tool-ocamldoc/.ignore
@@ -1,3 +1,4 @@
*.html
*.sty
*.css
+ocamldoc.out
diff --git a/tools/Makefile.shared b/tools/Makefile.shared
index 31cbb6a08..9c23b4467 100644
--- a/tools/Makefile.shared
+++ b/tools/Makefile.shared
@@ -35,7 +35,7 @@ opt.opt: ocamldep.opt
CAMLDEP_OBJ=depend.cmo ocamldep.cmo
CAMLDEP_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \
- linenum.cmo warnings.cmo location.cmo longident.cmo \
+ warnings.cmo location.cmo longident.cmo \
syntaxerr.cmo parser.cmo lexer.cmo parse.cmo
ocamldep: depend.cmi $(CAMLDEP_OBJ)
@@ -60,7 +60,7 @@ install::
CSLPROF=ocamlprof.cmo
CSLPROF_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \
- linenum.cmo warnings.cmo location.cmo longident.cmo \
+ warnings.cmo location.cmo longident.cmo \
syntaxerr.cmo parser.cmo lexer.cmo parse.cmo
ocamlprof: $(CSLPROF) profiling.cmo
@@ -126,7 +126,7 @@ clean::
# Converter olabl/ocaml 2.99 to ocaml 3
OCAML299TO3= lexer299.cmo ocaml299to3.cmo
-LIBRARY3= misc.cmo warnings.cmo linenum.cmo location.cmo
+LIBRARY3= misc.cmo warnings.cmo location.cmo
ocaml299to3: $(OCAML299TO3)
$(CAMLC) $(LINKFLAGS) -o ocaml299to3 $(LIBRARY3) $(OCAML299TO3)
@@ -159,7 +159,7 @@ clean::
# Insert labels following an interface file (upgrade 3.02 to 3.03)
ADDLABELS_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \
- linenum.cmo warnings.cmo location.cmo longident.cmo \
+ warnings.cmo location.cmo longident.cmo \
syntaxerr.cmo parser.cmo lexer.cmo parse.cmo
addlabels: addlabels.cmo
diff --git a/toplevel/opttoploop.ml b/toplevel/opttoploop.ml
index 97e715f2c..8771387cf 100644
--- a/toplevel/opttoploop.ml
+++ b/toplevel/opttoploop.ml
@@ -412,7 +412,8 @@ let loop ppf =
fprintf ppf " OCaml version %s - native toplevel@.@." Config.version;
initialize_toplevel_env ();
let lb = Lexing.from_function refill_lexbuf in
- Location.input_name := "";
+ Location.init lb "//toplevel//";
+ Location.input_name := "//toplevel//";
Location.input_lexbuf := Some lb;
Sys.catch_break true;
load_ocamlinit ppf;
diff --git a/toplevel/toploop.ml b/toplevel/toploop.ml
index 8a679af39..385aae463 100644
--- a/toplevel/toploop.ml
+++ b/toplevel/toploop.ml
@@ -403,7 +403,8 @@ let loop ppf =
fprintf ppf " OCaml version %s@.@." Config.version;
initialize_toplevel_env ();
let lb = Lexing.from_function refill_lexbuf in
- Location.input_name := "";
+ Location.init lb "//toplevel//";
+ Location.input_name := "//toplevel//";
Location.input_lexbuf := Some lb;
Sys.catch_break true;
load_ocamlinit ppf;