summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2003-06-12 12:52:17 +0000
committerDamien Doligez <damien.doligez-inria.fr>2003-06-12 12:52:17 +0000
commit7907414f8fa7a982ec1e1afc6eaa4516f550cd41 (patch)
tree9a42dfc0f612d596938fde9b0137e450b24e18ed
parentdd0fe66f95d286622af235a0dfce21f8c33159db (diff)
changement .types -> .annot + format
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5594 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--driver/main_args.ml2
-rw-r--r--driver/optmain.ml2
-rw-r--r--emacs/caml-types.el40
-rw-r--r--typing/stypes.ml5
-rw-r--r--typing/typemod.ml2
5 files changed, 40 insertions, 11 deletions
diff --git a/driver/main_args.ml b/driver/main_args.ml
index b112c60e1..786fa8dc3 100644
--- a/driver/main_args.ml
+++ b/driver/main_args.ml
@@ -74,7 +74,7 @@ struct
"<lib> Use the dynamically-loaded library <lib>";
"-dllpath", Arg.String F._dllpath,
"<dir> Add <dir> to the run-time search path for shared libraries";
- "-dtypes", Arg.Unit F._dtypes, " Save type information in <filename>.types";
+ "-dtypes", Arg.Unit F._dtypes, " Save type information in <filename>.annot";
"-g", Arg.Unit F._g, " Save debugging information";
"-i", Arg.Unit F._i, " Print the types";
"-I", Arg.String F._I,
diff --git a/driver/optmain.ml b/driver/optmain.ml
index a321fa2b7..a6d9d387b 100644
--- a/driver/optmain.ml
+++ b/driver/optmain.ml
@@ -89,7 +89,7 @@ let main () =
"-compact", Arg.Clear optimize_for_speed,
" Optimize code size rather than speed";
"-dtypes", Arg.Set save_types,
- " Save type information in <filename>.types";
+ " Save type information in <filename>.annot";
"-i", Arg.Set print_types, " Print the types";
"-I", Arg.String(fun dir -> include_dirs := dir :: !include_dirs),
"<dir> Add <dir> to the list of include directories";
diff --git a/emacs/caml-types.el b/emacs/caml-types.el
index 3a634e20b..bfa99be18 100644
--- a/emacs/caml-types.el
+++ b/emacs/caml-types.el
@@ -19,7 +19,7 @@
; Load this file in your emacs, then C-c C-t will show you the
; type of the expression (or pattern) that contains the cursor.
; The expression is highlighted in the current buffer.
-; The type is highlighted in "foo.types" (if your file is "foo.ml"),
+; The type is highlighted in "foo.annot" (if your file is "foo.ml"),
; which is convenient when the type doesn't fit on a line.
@@ -36,16 +36,43 @@
; in the file, up to where the type checker failed.
; . To get rid of the highlighting, put the cursor in a comment
; and type C-c C-t.
-; . The mark in the .types file is set to the beginning of the
+; . The mark in the foo.annot file is set to the beginning of the
; type, so you can type C-x C-x in that file to view the type.
; TO DO:
-; - make emacs scroll the .types file to show the type
+; - make emacs scroll the foo.annot file to show the type
; - (?) integrate this file into caml.el
-
+
+; Format of the *.annot files:
+
+; file ::= block *
+; block ::= position <SP> position <LF> annotation *
+; position ::= filename <SP> num <SP> num <SP> num
+; annotation ::= keyword open-paren <LF> <SP> <SP> data <LF> close-paren
+
+; <SP> is a space character (ASCII 0x20)
+; <LF> is a line-feed character (ASCII 0x0A)
+; num is a sequence of decimal digits
+; filename is a string with the lexical conventions of O'Caml
+; open-paren is an open parenthesis (ASCII 0x28)
+; close-paren is a closed parenthesis (ASCII 0x29)
+; data is any sequence of characters where <LF> is always followed by
+; at least two space characters.
+
+; in each block, the two positions are respectively the start and the
+; end of the range described by the block.
+; in a position, the filename is the name of the file, the first num
+; is the line number, the second num is the offset of the beginning
+; of the line, the third num is the offset of the position itself.
+; the char number within the line is the difference between the third
+; and second nums.
+
+; For the moment, the only possible keyword is "type".
+
+
; (global-set-key "\C-c\C-t" 'caml-types-show-type)
@@ -75,7 +102,7 @@
(target-bol (line-beginning-position))
(target-cnum (point))
(type-file (concat (file-name-sans-extension (buffer-file-name))
- ".types"))
+ ".annot"))
(type-date (nth 5 (file-attributes type-file)))
(type-buf (caml-types-find-file type-file)))
(if (caml-types-date< type-date target-date)
@@ -94,7 +121,8 @@
(right (caml-types-get-pos target-buf
(nth 2 loc) (nth 3 loc))))
(move-overlay caml-types-expr-ovl left right target-buf))
- (forward-line 2)
+ (re-search-forward "^type(") ;; not strictly correct
+ (forward-line 1)
(re-search-forward " \\(\\([^\n)]\\|.)\\|\n[^)]\\)*\\)\n)")
(move-overlay caml-types-type-ovl (match-beginning 1) (match-end 1)
type-buf)
diff --git a/typing/stypes.ml b/typing/stypes.ml
index b4d1837ff..e69438d1e 100644
--- a/typing/stypes.ml
+++ b/typing/stypes.ml
@@ -65,6 +65,8 @@ let print_position pp pos =
fprintf pp "%S %d %d %d" pos.pos_fname pos.pos_lnum pos.pos_bol pos.pos_cnum;
;;
+(* The format of the annotation file is documented in emacs/caml-types.el. *)
+
let print_info pp ti =
match ti with
Ti_class _ | Ti_mod _ -> ()
@@ -73,7 +75,7 @@ let print_info pp ti =
print_position pp loc.loc_start;
fprintf pp " ";
print_position pp loc.loc_end;
- fprintf pp "@.(@. ";
+ fprintf pp "@.type(@. ";
Printtyp.type_expr pp typ;
fprintf pp "@.)@.";
;;
@@ -90,4 +92,3 @@ let dump filename =
List.iter (print_info pp) info
end;
;;
-
diff --git a/typing/typemod.ml b/typing/typemod.ml
index 503b49785..d0fc5b2e8 100644
--- a/typing/typemod.ml
+++ b/typing/typemod.ml
@@ -531,7 +531,7 @@ let type_implementation sourcefile prefixname modulename initial_env ast =
Typecore.reset_delayed_checks ();
let (str, sg, finalenv) =
Misc.try_finally (fun () -> type_structure initial_env ast)
- (fun () -> Stypes.dump (prefixname ^ ".types"))
+ (fun () -> Stypes.dump (prefixname ^ ".annot"))
in
Typecore.force_delayed_checks ();
if !Clflags.print_types then