Skip to content

Commit ee34542

Browse files
committed
WIP #2
1 parent 1ae0d71 commit ee34542

File tree

3 files changed

+39
-13
lines changed

3 files changed

+39
-13
lines changed

emacs/merlin.el

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1043,7 +1043,7 @@ errors in the fringe. If VIEW-ERRORS-P is non-nil, display a count of them."
10431043
(prefix (car ident-))
10441044
(pos (merlin-unmake-point (point)))
10451045
(data (merlin-send-command
1046-
(if merlin-completion-with-doc
1046+
(if (and merlin-completion-with-doc);; (> (length ident) 0))
10471047
`(complete prefix ,ident at ,pos with doc)
10481048
`(complete prefix ,ident at ,pos))))
10491049
;; all classic entries

src/analysis/track_definition.ml

Lines changed: 36 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -651,18 +651,42 @@ let get_doc ~project ~env ~local_defs ~comments ~pos source =
651651
Fluid.let' cfg_cmt_path (Project.cmt_path project) @@ fun () ->
652652
Fluid.let' loadpath (Project.cmt_path project) @@ fun () ->
653653
Fluid.let' last_location Location.none @@ fun () ->
654-
match
654+
let store, location =
655+
let is_cached (namespace,path,_) =
656+
let ident = Path.head path in
657+
try
658+
if not (Ident.persistent ident) then
659+
raise Not_found;
660+
let filename = Utils.find_file ~with_fallback:true
661+
(File.CMTI (Ident.name ident)) in
662+
let cmt = Cmt_cache.read filename in
663+
let key = (namespace,List.tl (Path.to_string_list path)) in
664+
match Hashtbl.find cmt.Cmt_cache.doc_table key with
665+
| store -> `Some store
666+
| exception Not_found ->
667+
let store = ref None in
668+
Hashtbl.add cmt.Cmt_cache.doc_table key store;
669+
`None store
670+
with _ -> `None (ref None)
671+
in
655672
match path with
656-
| `Completion_entry entry -> from_completion_entry ~pos ~lazy_trie entry
673+
| `Completion_entry entry ->
674+
begin match is_cached entry with
675+
| `Some cache -> cache, `Cached !cache
676+
| `None store -> store, from_completion_entry ~pos ~lazy_trie entry
677+
end
657678
| `User_input path ->
658679
let lid = Longident.parse path in
659680
begin match inspect_context browse path pos with
660-
| None -> `Found { Location. loc_start=pos; loc_end=pos ; loc_ghost=true }
661-
| Some ctxt ->
662-
info_log "looking for the doc of '%s'" path ;
663-
from_longident ~pos ~env ~lazy_trie ctxt `MLI lid
681+
| None -> ref None, `Found { Location. loc_start=pos; loc_end=pos ; loc_ghost=true }
682+
| Some ctxt ->
683+
info_log "looking for the doc of '%s'" path ;
684+
ref None, from_longident ~pos ~env ~lazy_trie ctxt `MLI lid
664685
end
665-
with
686+
in
687+
match location with
688+
| `Cached (Some doc) -> `Found doc
689+
| `Cached None -> `No_documentation
666690
| `Found loc ->
667691
let comments =
668692
match File_switching.where_am_i () with
@@ -671,11 +695,11 @@ let get_doc ~project ~env ~local_defs ~comments ~pos source =
671695
let {Cmt_cache. cmt_infos} = Cmt_cache.read cmt_path in
672696
cmt_infos.Cmt_format.cmt_comments
673697
in
674-
begin match
675-
Ocamldoc.associate_comment comments loc (Fluid.get last_location)
676-
with
677-
| None, _ -> `No_documentation
678-
| Some doc, _ -> `Found doc
698+
let doc, _ = Ocamldoc.associate_comment comments loc (Fluid.get last_location) in
699+
store := doc;
700+
begin match doc with
701+
| None -> `No_documentation
702+
| Some doc -> `Found doc
679703
end
680704
| `File_not_found _
681705
| `Not_found _

src/ocaml_aux/cmt_cache.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,7 @@ type trie = (Location.t * namespace * node) list String.Map.t
5151
type cmt_item = {
5252
cmt_infos : Cmt_format.cmt_infos ;
5353
mutable location_trie : trie ;
54+
doc_table: (namespace * string list, string option ref) Hashtbl.t;
5455
}
5556

5657
include File_cache.Make (struct
@@ -59,5 +60,6 @@ include File_cache.Make (struct
5960
let read file = {
6061
cmt_infos = Cmt_format.read_cmt file ;
6162
location_trie = String.Map.empty ;
63+
doc_table = Hashtbl.create 7 ;
6264
}
6365
end)

0 commit comments

Comments
 (0)