@@ -32,57 +32,12 @@ include Common.Let_syntax
3232
3333let in_group (t , info ) = (Term.Group. Term t, info)
3434
35- let make_cache (config : Dune_config.t ) =
36- let make_cache () =
37- let command_handler (Cache. Dedup file ) =
38- match Build_system. get_cache () with
39- | None -> Code_error. raise " deduplication message and no caching" []
40- | Some caching ->
41- Scheduler. send_sync_task (fun () ->
42- let (module Caching : Cache.Caching ) = caching.cache in
43- match Cached_digest. peek_file (Path. build file.path) with
44- | None -> ()
45- | Some d when not (Digest. equal d file.digest) -> ()
46- | _ -> Caching.Cache. deduplicate Caching. cache file)
47- in
48- match config.cache_transport with
49- | Dune_config.Caching.Transport. Direct ->
50- Log. info [ Pp. text " enable binary cache in direct access mode" ];
51- let cache =
52- Result. ok_exn
53- (Result. map_error
54- ~f: (fun s -> User_error. E (User_error. make [ Pp. text s ]))
55- (Cache.Local. make ?duplication_mode:config.cache_duplication
56- ~command_handler () ))
57- in
58- Cache. make_caching (module Cache. Local ) cache
59- | Daemon ->
60- Log. info [ Pp. text " enable binary cache in daemon mode" ];
61- let cache =
62- Result. ok_exn
63- (Cache.Client. make ?duplication_mode:config.cache_duplication
64- ~command_handler () )
65- in
66- Cache. make_caching (module Cache. Client ) cache
67- in
68- Fiber. return
69- (match config.cache_mode with
70- | Dune_config.Caching.Mode. Enabled ->
71- Some
72- { Build_system. cache = make_cache ()
73- ; check_probability = config.cache_check_probability
74- }
75- | Dune_config.Caching.Mode. Disabled ->
76- Log. info [ Pp. text " disable binary cache" ];
77- None )
78-
7935module Main = struct
8036 include Dune_rules. Main
8137
82- let setup common config =
38+ let setup common ( config : Dune_config.t ) =
8339 let open Fiber.O in
84- let * caching = make_cache config
85- and * conf = Memo.Build. run (Dune_rules.Dune_load. load () )
40+ let * conf = Memo.Build. run (Dune_rules.Dune_load. load () )
8641 and * contexts = Memo.Build. run (Context.DB. all () ) in
8742 let stats = Common. stats common in
8843 List. iter contexts ~f: (fun (ctx : Context.t ) ->
@@ -91,8 +46,25 @@ module Main = struct
9146 [ Pp. box ~indent: 1
9247 (Pp. text " Dune context:" ++ Pp. cut ++ Dyn. pp (Context. to_dyn ctx))
9348 ]);
49+ (* CR-soon amokhov: Right now, types [Dune_config.Caching.Duplication.t] and
50+ [Dune_cache_storage.Mode.t] are the same. They will be unified after
51+ removing the cache daemon and adapting the configuration format. *)
52+ let cache_config =
53+ match config.cache_mode with
54+ | Disabled -> Dune_cache.Config. Disabled
55+ | Enabled ->
56+ Enabled
57+ { storage_mode =
58+ (match config.cache_duplication with
59+ | None
60+ | Some Hardlink ->
61+ Dune_cache_storage.Mode. Hardlink
62+ | Some Copy -> Copy )
63+ ; check_probability = config.cache_check_probability
64+ }
65+ in
9466 init_build_system ~stats ~sandboxing_preference: config.sandboxing_preference
95- ~caching ~conf ~contexts
67+ ~cache_config ~conf ~contexts
9668end
9769
9870module Scheduler = struct
0 commit comments