Skip to content

Commit

Permalink
Better fix of the watch mode (#1839)
Browse files Browse the repository at this point in the history
Signed-off-by: Jeremie Dimino <[email protected]>
  • Loading branch information
jeremiedimino committed Feb 13, 2019
1 parent 485a046 commit 0c5ff45
Show file tree
Hide file tree
Showing 2 changed files with 17 additions and 13 deletions.
2 changes: 1 addition & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
1.7.1 (13/02/2019)
------------------

- Fix the watch mode (#1837, fix #1836, @diml)
- Fix the watch mode (#1837, #1839, fix #1836, @diml)

- Configurator: Fix misquoting when running pkg-config (#1835, fix #1833,
@Chris00)
Expand Down
28 changes: 16 additions & 12 deletions src/memo/memo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,19 @@ end = struct
let is_current t = !t
end

let reset = Run.restart
(* We can get rid of this once we use the memoization system more
pervasively and all the dependencies are properly specified *)
module Caches = struct
let cleaners = ref []
let register ~clear =
cleaners := clear :: !cleaners
let clear () =
List.iter !cleaners ~f:(fun f -> f ())
end

let reset () =
Caches.clear ();
Run.restart ()

module M = struct
module Generic_dag = Dag
Expand Down Expand Up @@ -166,16 +178,6 @@ module Cached_value = struct
t.calculated_at <- Run.current ();
Some t.data
end

(* We don't use this version of [get] yet as all the dependencies
are not yet properly specified. *)
let _ = get

let get t =
if Run.is_current t.calculated_at then
Fiber.return (Some t.data)
else
Fiber.return None
end

let ser_input (type a) (node : (a, _) Dep_node.t) =
Expand Down Expand Up @@ -301,7 +303,9 @@ module Make_gen
(match Visibility.visibility with
| Public -> Spec.register spec
| Private -> ());
{ cache = Table.create 1024
let cache = Table.create 1024 in
Caches.register ~clear:(fun () -> Table.clear cache);
{ cache
; spec
; fdecl
}
Expand Down

0 comments on commit 0c5ff45

Please sign in to comment.