diff --git a/bin/toplevel_init_file.ml b/bin/toplevel_init_file.ml index 1e858efd3caf..401a2618f76f 100644 --- a/bin/toplevel_init_file.ml +++ b/bin/toplevel_init_file.ml @@ -18,20 +18,21 @@ let man = let info = Term.info "toplevel-init-file" ~doc ~man let link_deps link ~lib_config = - List.map link ~f:(fun t -> + List.concat_map link ~f:(fun t -> Dune.Lib.link_deps t Dune.Link_mode.Byte lib_config) - |> List.flatten let term = let+ common = Common.term - and+ dir = Arg.(value & pos 0 string "" & Arg.info [] ~docv:"DIR") in + and+ dir = Arg.(value & pos 0 string "" & Arg.info [] ~docv:"DIR") + and+ ctx_name = + Common.context_arg ~doc:{|Select context where to build/run utop.|} + in Common.set_common common ~targets:[]; Scheduler.go ~common (fun () -> let open Fiber.O in let* setup = Import.Main.setup common in let sctx = - Dune.Context_name.Map.find setup.scontexts Dune.Context_name.default - |> Option.value_exn + Dune.Context_name.Map.find setup.scontexts ctx_name |> Option.value_exn in let dir = Path.Build.relative @@ -48,11 +49,8 @@ let term = let* () = do_build (List.map files ~f:(fun f -> Target.File f)) in let files_to_load = List.filter files ~f:(fun p -> - match Path.extension p with - | ".cma" - | ".cmo" -> - true - | _ -> false) + let ext = Path.extension p in + ext = Dune.Mode.compiled_lib_ext Byte || ext = Dune.Cm_kind.ext Cmo) in Dune.Toplevel.print_toplevel_init_file ~include_paths ~files_to_load; Fiber.return ()) diff --git a/src/dune/utop.mli b/src/dune/utop.mli index 3d5012a66ab8..30d6b180f196 100644 --- a/src/dune/utop.mli +++ b/src/dune/utop.mli @@ -8,7 +8,6 @@ val utop_exe : string val is_utop_dir : Path.Build.t -> bool -val libs_under_dir : - Super_context.t -> db:Lib.DB.t -> dir:Import.Path.t -> Lib.L.t +val libs_under_dir : Super_context.t -> db:Lib.DB.t -> dir:Path.t -> Lib.L.t val setup : Super_context.t -> dir:Path.Build.t -> unit