Skip to content

Commit

Permalink
added explicit memoization cached interface and type
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Horn <dyn-git@rudi-horn.de>
  • Loading branch information
Rudi Horn committed Nov 8, 2018
1 parent dea493c commit 734fcdf
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 1 deletion.
2 changes: 1 addition & 1 deletion src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -398,7 +398,7 @@ type t =
; (* Package files are part of *)
packages : Package.Name.t Path.Table.t
(* memoized functions *)
; cache_static_deps : (Memoization_cached.Id.t * Static_deps.t Fiber.t) -> (Static_deps.t Fiber.t)
; cache_static_deps : Static_deps.t Memoization_cached.t
; prepare_rule_def : (Internal_rule.t * (unit, Action.t) Build.t, Action.t * Deps.t) Fdecl.comp
; build_rule_def : (Internal_rule.t * (unit, Action.t) Build.t, Action.t * Deps.t) Fdecl.comp
; build_file_def : (Path.t * Loc.t option, unit) Fdecl.comp
Expand Down
2 changes: 2 additions & 0 deletions src/memoization_cached.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@ open Memoization_specs

module Id = Id.Make ()

type 'a t = Id.t * 'a Fiber.t -> 'a Fiber.t

let id_input_spec =
let ser x = Id.to_int x |> string_of_int in
let ne x y = x <> y in
Expand Down
5 changes: 5 additions & 0 deletions src/memoization_cached.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
type 'a t

val cached : unit -> 'a t

val cache : 'a t -> 'a Fiber.t -> 'a Fiber.t

0 comments on commit 734fcdf

Please sign in to comment.