Skip to content

Commit

Permalink
Enhance typing of typer cache
Browse files Browse the repository at this point in the history
  • Loading branch information
3Rafal committed Dec 12, 2023
1 parent 736ba53 commit de8215b
Show file tree
Hide file tree
Showing 3 changed files with 23 additions and 14 deletions.
18 changes: 11 additions & 7 deletions src/kernel/mpipeline.ml
Original file line number Diff line number Diff line change
Expand Up @@ -102,7 +102,7 @@ type t = {

ppx_cache_hit : bool ref;
reader_cache_hit : bool ref;
buffer_cache_stats : string ref;
typer_cache_stats : Mtyper.typer_cache_stats ref;
}

let raw_source t = t.raw_source
Expand Down Expand Up @@ -237,7 +237,7 @@ let process
?(error_time=ref 0.0)
?(ppx_cache_hit = ref false)
?(reader_cache_hit = ref false)
?(buffer_cache_stats = ref "")
?(typer_cache_stats = ref Mtyper.Miss)
?for_completion
config raw_source =
let state = match state with
Expand Down Expand Up @@ -313,12 +313,12 @@ let process
Mocaml.setup_typer_config config;
let result = Mtyper.run config parsetree in
let errors = timed_lazy error_time (lazy (Mtyper.get_errors result)) in
buffer_cache_stats := Mtyper.get_cache_stat result;
typer_cache_stats := Mtyper.get_cache_stat result;
{ Typer. errors; result }
)) in
{ config; state; raw_source; source; reader; ppx; typer;
pp_time; reader_time; ppx_time; typer_time; error_time;
ppx_cache_hit; reader_cache_hit; buffer_cache_stats }
ppx_cache_hit; reader_cache_hit; typer_cache_stats }

let make config source =
process (Mconfig.normalize config) source
Expand Down Expand Up @@ -348,7 +348,11 @@ let cache_information t =
let cmi = ("cmi", List.map ~f:fmt_file (Cmi_cache.get_cache_stats ())) in
Cmt_cache.clear_cache_stats ();
Cmi_cache.clear_cache_stats ();
let buffer = ("buffer", [
"stats", !(t.buffer_cache_stats)
let typer_stats_msg =
match !(t.typer_cache_stats) with
| Miss -> "miss"
| Hit { reused; typed } -> Printf.sprintf "reused %d items, typed %d new items" reused typed in
let typer = ("buffer", [
"stats", typer_stats_msg
]) in
[phase; cmt; cmi; buffer]
[phase; cmt; cmi; typer]
15 changes: 9 additions & 6 deletions src/kernel/mtyper.ml
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,8 @@ type typedtree = [
| `Implementation of Typedtree.structure
]

type typer_cache_stats = Miss | Hit of { reused : int; typed : int }

let cache = s_ref None

let fresh_env config =
Expand Down Expand Up @@ -51,7 +53,7 @@ type result = {
| `Implementation of
(Parsetree.structure_item, Typedtree.structure_item) item list
];
cache_stat : string
cache_stat : typer_cache_stats
}

let initial_env res = res.initial_env
Expand All @@ -65,10 +67,11 @@ let compatible_prefix result_items tree_items =
&& compare ritem.parsetree_item pitem = 0 ->
aux (ritem :: acc) (ritems, pitems)
| (_, pitems) ->
let cache_stat = Printf.sprintf "reusing %d items, %d new items to type"
(List.length acc) (List.length pitems) in
let reused = List.length acc in
let typed = List.length pitems in
let cache_stat = Hit { reused; typed } in
log ~title:"compatible_prefix" "reusing %d items, %d new items to type"
(List.length acc) (List.length pitems);
reused typed;
acc, pitems, cache_stat
in
aux [] (result_items, tree_items)
Expand Down Expand Up @@ -111,7 +114,7 @@ let type_implementation config caught parsetree =
let prefix, parsetree, cache_stat =
match prefix with
| Some (`Implementation items) -> compatible_prefix items parsetree
| Some (`Interface _) | None -> ([], parsetree, "miss")
| Some (`Interface _) | None -> ([], parsetree, Miss)
in
let env', snap', stamp', warn' = match prefix with
| [] -> (env0, snap0, stamp0, Warnings.backup ())
Expand All @@ -132,7 +135,7 @@ let type_interface config caught parsetree =
let prefix, parsetree, cache_stat =
match prefix with
| Some (`Interface items) -> compatible_prefix items parsetree
| Some (`Implementation _) | None -> ([], parsetree, "miss")
| Some (`Implementation _) | None -> ([], parsetree, Miss)
in
let env', snap', stamp', warn' = match prefix with
| [] -> (env0, snap0, stamp0, Warnings.backup ())
Expand Down
4 changes: 3 additions & 1 deletion src/kernel/mtyper.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@ type typedtree = [
| `Implementation of Typedtree.structure
]

type typer_cache_stats = Miss | Hit of { reused : int; typed : int }

val run : Mconfig.t -> Mreader.parsetree -> result

val get_env : ?pos:Msource.position -> result -> Env.t
Expand All @@ -24,7 +26,7 @@ val get_errors : result -> exn list

val initial_env : result -> Env.t

val get_cache_stat : result -> string
val get_cache_stat : result -> typer_cache_stats

(** Heuristic to find suitable environment to complete / type at given position.
* 1. Try to find environment near given cursor.
Expand Down

0 comments on commit de8215b

Please sign in to comment.