Skip to content

Commit

Permalink
Add support for loading libraries from toplevel
Browse files Browse the repository at this point in the history
* Start work on loading dune libraries from toplevel
* Finish draft version of toplevel-init-file
* Add toplevel loading script
* Add install stanza for dune.mlt
* Remove dependency on Unix in the toplevel script
* Add documentation for toplevel integration
* Add a very basic test for toplevel-init-file
  • Loading branch information
mbernat committed Dec 5, 2019
1 parent 170f319 commit ff4a9a2
Show file tree
Hide file tree
Showing 14 changed files with 143 additions and 0 deletions.
5 changes: 5 additions & 0 deletions bin/dune
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,11 @@
(files
(dune.exe as dune)))

(install
(section lib_root)
(package dune)
(files (dune.mlt as toplevel/dune)))

(deprecated_library_name
(old_public_name dune.configurator)
(new_public_name dune-configurator))
26 changes: 26 additions & 0 deletions bin/dune.mlt
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
let exception AbnormalExit of string * int in
let run_and_get_lines cmd tmp_filename =
let err_code = Sys.command (cmd ^ " > " ^ tmp_filename) in
if err_code != 0 then
raise (AbnormalExit (cmd, err_code));
let inp = open_in tmp_filename in
let res = ref [] in
let () = try
while true do
let line = input_line inp in
res := List.cons line !res
done
with End_of_file ->
close_in inp
in
List.rev(!res)
in
let exec s =
let l = Lexing.from_string s in
let ph = !Toploop.parse_toplevel_phrase l in
let fmt = Format.make_formatter (fun _ _ _ -> ()) (fun _ -> ()) in
let _ = Toploop.execute_phrase false fmt ph in ()
in
let tmp_filename = Filename.temp_file "libraries" "top" in
let lines = run_and_get_lines "dune.exe toplevel-init-file" tmp_filename in
List.iter (fun l -> exec l) lines
1 change: 1 addition & 0 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -154,6 +154,7 @@ let all =
; Compute.command
; Upgrade.command
; Cache_daemon.command
; Toplevel_init_file.command
]

let default =
Expand Down
54 changes: 54 additions & 0 deletions bin/toplevel_init_file.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
open Stdune
open Import

let doc = "Print a list of toplevel directives for including directories and loading cma files."

let man =
[ `S "DESCRIPTION"
; `P {|Print a list of toplevel directives for including directories and loading cma files.|}
; `P
{|The output of $(b,dune toplevel-init-file) should be evaluated in a toplevel
to make a library available there.|}
; `Blocks Common.help_secs
]

let info = Term.info "toplevel-init-file" ~doc ~man

let link_deps link ~lib_config =
List.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
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
in
let dir =
Path.Build.relative
(Super_context.build_dir sctx)
(Common.prefix_target common dir)
in
let scope = Super_context.find_scope_by_dir sctx dir in
let db = Dune.Scope.libs scope in
let libs = Dune.Utop.libs_under_dir sctx ~db ~dir:(Path.build dir) in
let requires = Dune.Lib.closure ~linking:true libs |> Result.ok_exn in
let include_paths = Dune.Lib.L.include_paths requires in
let lib_config = sctx |> Super_context.context |> Context.lib_config in
let files = link_deps requires ~lib_config in
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)
in
Dune.Toplevel.print_toplevel_init_file ~include_paths ~files_to_load;
Fiber.return ())

let command = (term, info)
9 changes: 9 additions & 0 deletions doc/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,15 @@
(package dune)
(files dune-subst.1))

(rule
(with-stdout-to dune-toplevel-init-file.1
(run dune toplevel-init-file --help=groff)))

(install
(section man)
(package dune)
(files dune-toplevel-init-file.1))

(rule
(with-stdout-to dune-uninstall.1
(run dune uninstall --help=groff)))
Expand Down
1 change: 1 addition & 0 deletions doc/index.rst
Original file line number Diff line number Diff line change
Expand Up @@ -29,3 +29,4 @@ Welcome to dune's documentation!
known-issues
migration
caching
toplevel-integration
14 changes: 14 additions & 0 deletions doc/toplevel-integration.rst
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
********************
Toplevel integration
********************

It's possible to load dune projects in any toplevel. This is achieved in two stages.

First, `dune toplevel-init-file` builds the project and produces a list of toplevel pragmas
(#directory and #load). Copying the output of this command to a toplevel lets you
interact with the project's modules.

Second, to enhance usability, dune also provides a toplevel script, which does the above
manual work for you. To use it, make sure to have `topfind` available in your toplevel by
invoking `#use "topfind";;`. Afterwards you can run `#use "dune";;` and your
modules should be available.
7 changes: 7 additions & 0 deletions src/dune/toplevel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,13 @@ let setup_rules t =
(Build.symlink ~src:(Path.build src) ~dst);
setup_module_rules t

let print_toplevel_init_file ~include_paths ~files_to_load =
let includes = Path.Set.to_list include_paths in
List.iter includes ~f:(fun p ->
print_endline("#directory \"" ^ Path.to_absolute_filename p ^ "\";;"));
List.iter files_to_load ~f:(fun p ->
print_endline("#load \"" ^ Path.to_absolute_filename p ^ "\";;"))

module Stanza = struct
let setup ~sctx ~dir ~(toplevel : Dune_file.Toplevel.t) =
let source = Source.of_stanza ~dir ~toplevel in
Expand Down
2 changes: 2 additions & 0 deletions src/dune/toplevel.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@ val setup_rules : t -> unit

val make : cctx:Compilation_context.t -> source:Source.t -> t

val print_toplevel_init_file : include_paths:Path.Set.t -> files_to_load:Path.t list -> unit

module Stanza : sig
val setup :
sctx:Super_context.t
Expand Down
2 changes: 2 additions & 0 deletions src/dune/utop.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +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 setup : Super_context.t -> dir:Path.Build.t -> unit
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -1680,6 +1680,14 @@
test-cases/tests-stanza-action-syntax-version
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(rule
(alias toplevel-integration)
(deps (package dune) (source_tree test-cases/toplevel-integration))
(action
(chdir
test-cases/toplevel-integration
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(rule
(alias toplevel-stanza)
(deps (package dune) (source_tree test-cases/toplevel-stanza))
Expand Down Expand Up @@ -2138,6 +2146,7 @@
(alias tests-stanza)
(alias tests-stanza-action)
(alias tests-stanza-action-syntax-version)
(alias toplevel-integration)
(alias toplevel-stanza)
(alias trace-file)
(alias transitive-deps-mode)
Expand Down Expand Up @@ -2346,6 +2355,7 @@
(alias tests-stanza)
(alias tests-stanza-action)
(alias tests-stanza-action-syntax-version)
(alias toplevel-integration)
(alias toplevel-stanza)
(alias trace-file)
(alias transitive-deps-mode)
Expand Down
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/toplevel-integration/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(library
(name test)
(public_name test))
9 changes: 9 additions & 0 deletions test/blackbox-tests/test-cases/toplevel-integration/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
Test toplevel-init-file on empty project
----------------------------------------------------
$ dune toplevel-init-file
Info: Creating file dune-project with this contents:
| (lang dune 2.1)
| (name test)
#directory "$TESTCASE_ROOT/_build/default/.test.objs/byte";;
#directory "$TESTCASE_ROOT/_build/default/.test.objs/native";;
#load "$TESTCASE_ROOT/_build/default/test.cma";;
Empty file.

0 comments on commit ff4a9a2

Please sign in to comment.