Skip to content

Commit

Permalink
Merge branch 'master' into explicitly-pass-installed-binaries
Browse files Browse the repository at this point in the history
  • Loading branch information
aalekseyev authored May 1, 2019
2 parents 7a9e5c7 + 758b213 commit 3d77298
Show file tree
Hide file tree
Showing 32 changed files with 184 additions and 56 deletions.
16 changes: 13 additions & 3 deletions src/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -830,6 +830,16 @@ let parse ~dir ~lang ~packages ~file =
in
let allow_approx_merlin =
Option.value ~default:false allow_approx_merlin in
let packages =
match version with
| None -> packages
| Some version ->
let version = Some (version, Package.Version_source.Project) in
Package.Name.Map.map packages ~f:(fun p ->
match p.version with
| Some _ -> p
| None -> { p with version })
in
{ name
; root = dir
; version
Expand Down Expand Up @@ -894,7 +904,7 @@ let load ~dir ~files =
String.Set.fold files ~init:[] ~f:(fun fn acc ->
match Filename.split_extension fn with
| (pkg, ".opam") when pkg <> "" ->
let version_from_opam_file =
let version =
let open Option.O in
let* opam =
let opam_file = Path.Source.relative dir fn in
Expand All @@ -909,15 +919,15 @@ let load ~dir ~files =
in
let* version = Opam_file.get_field opam "version" in
match version with
| String (_, s) -> Some s
| String (_, s) -> Some (s, Package.Version_source.Package)
| _ -> None
in
let name = Package.Name.of_string pkg in
(name,
{ Package.
name
; path = dir
; version_from_opam_file
; version
}) :: acc
| _ -> acc)
|> Package.Name.Map.of_list_exn
Expand Down
61 changes: 27 additions & 34 deletions src/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -58,42 +58,35 @@ let gen_dune_package sctx ~version ~(pkg : Local_package.t) =
Build.write_file_dyn dune_package_file
|> Super_context.add_rule sctx ~dir:ctx.build_dir

let version_from_dune_project sctx ~(pkg : Package.t) =
let dir = Path.append_source (Super_context.build_dir sctx) pkg.path in
let project = Scope.project (Super_context.find_scope_by_dir sctx dir) in
Dune_project.version project

type version_method =
| File of string
| From_dune_project
| From_metadata of Package.Version_source.t

let pkg_version sctx ~path ~(pkg : Package.t) =
match pkg.version_from_opam_file with
| Some s -> Build.return (Some s)
| None ->
let rec loop = function
| [] -> Build.return None
| candidate :: rest ->
match candidate with
| File fn ->
let p = Path.relative path fn in
Build.if_file_exists p
~then_:(Build.lines_of p
>>^ function
| ver :: _ -> Some ver
| _ -> Some "")
~else_:(loop rest)
| From_dune_project ->
match version_from_dune_project sctx ~pkg with
| None -> loop rest
| Some _ as x -> Build.return x
in
loop
[ File (Package.Name.version_fn pkg.name)
; From_dune_project
; File "version"
; File "VERSION"
]
let pkg_version ~path ~(pkg : Package.t) =
let rec loop = function
| [] -> Build.return None
| candidate :: rest ->
match candidate with
| File fn ->
let p = Path.relative path fn in
Build.if_file_exists p
~then_:(Build.lines_of p
>>^ function
| ver :: _ -> Some ver
| _ -> Some "")
~else_:(loop rest)
| From_metadata source ->
match pkg.version with
| Some (v, source') when source = source' -> Build.return (Some v)
| _ -> loop rest
in
loop
[ From_metadata Package
; File (Package.Name.version_fn pkg.name)
; From_metadata Project
; File "version"
; File "VERSION"
]

let init_meta sctx ~dir =
Local_package.defined_in sctx ~dir
Expand All @@ -105,7 +98,7 @@ let init_meta sctx ~dir =
let meta_template = Local_package.meta_template pkg in
let version =
let pkg = Local_package.package pkg in
let get = pkg_version sctx ~pkg ~path in
let get = pkg_version ~pkg ~path in
Super_context.Pkg_version.set sctx pkg get
in

Expand Down
4 changes: 2 additions & 2 deletions src/odoc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -251,10 +251,10 @@ let setup_toplevel_index_rule sctx =
let name = Package.Name.to_string name in
let link = sp {|<a href="%s/index.html">%s</a>|} name name in
let version_suffix =
match pkg.Package.version_from_opam_file with
match pkg.Package.version with
| None ->
""
| Some v ->
| Some (v, _) ->
sp {| <span class="version">%s</span>|} v
in
Some (sp "<li>%s%s</li>" link version_suffix))
Expand Down
29 changes: 21 additions & 8 deletions src/package.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,27 +26,40 @@ module Name = struct
module Infix = Comparable.Operators(T)
end

module Version_source = struct
type t =
| Package
| Project

let to_dyn t =
Dyn.Variant
((match t with
| Package -> "Package"
| Project -> "Project"),
[])
end

type t =
{ name : Name.t
; path : Path.Source.t
; version_from_opam_file : string option
{ name : Name.t
; path : Path.Source.t
; version : (string * Version_source.t) option
}

let hash { name; path; version_from_opam_file } =
let hash { name; path; version } =
Hashtbl.hash
( Name.hash name
, Path.Source.hash path
, Option.hash String.hash version_from_opam_file
, Hashtbl.hash version
)

let to_dyn { name; path; version_from_opam_file } =
let to_dyn { name; path; version } =
let open Dyn in
Record
[ "name", Name.to_dyn name
; "path", Path.Source.to_dyn path
; "version_from_opam_file"
, Option (Option.map ~f:(fun s -> String s) version_from_opam_file)
; "version",
Option (Option.map ~f:(fun (v, s) ->
Tuple [String v; Version_source.to_dyn s]) version)
]

let pp fmt t = Dyn.pp fmt (to_dyn t)
Expand Down
14 changes: 11 additions & 3 deletions src/package.mli
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,18 @@ module Name : sig
module Infix : Comparable.OPS with type t = t
end

module Version_source : sig
(** Wether this version comes from the project wide version or the
package particular version *)
type t =
| Package
| Project
end

type t =
{ name : Name.t
; path : Path.Source.t
; version_from_opam_file : string option
{ name : Name.t
; path : Path.Source.t
; version : (string * Version_source.t) option
}

val pp : Format.formatter -> t -> unit
Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -769,6 +769,14 @@
test-cases/include-loop
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

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

(alias
(name inline_tests)
(deps (package dune) (source_tree test-cases/inline_tests))
Expand Down Expand Up @@ -1506,6 +1514,7 @@
(alias glob-deps)
(alias ignored_subdirs)
(alias include-loop)
(alias include-qualified)
(alias inline_tests)
(alias install-dry-run)
(alias install-libdir)
Expand Down Expand Up @@ -1672,6 +1681,7 @@
(alias glob-deps)
(alias ignored_subdirs)
(alias include-loop)
(alias include-qualified)
(alias inline_tests)
(alias install-rule-order)
(alias install-with-var)
Expand Down
12 changes: 6 additions & 6 deletions test/blackbox-tests/test-cases/coq/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -46,9 +46,9 @@
$ dune build --root base --display short --debug-dependency-path @default
Entering directory 'base'
lib: [
"_build/install/default/lib/base/META" {"META"}
"_build/install/default/lib/base/dune-package" {"dune-package"}
"_build/install/default/lib/base/opam" {"opam"}
"_build/install/default/lib/base/META"
"_build/install/default/lib/base/dune-package"
"_build/install/default/lib/base/opam"
]
lib_root: [
"_build/install/default/lib/coq/user-contrib/basic/bar.vo" {"coq/user-contrib/basic/bar.vo"}
Expand All @@ -58,9 +58,9 @@
$ dune build --root rec_module --display short --debug-dependency-path @default
Entering directory 'rec_module'
lib: [
"_build/install/default/lib/rec/META" {"META"}
"_build/install/default/lib/rec/dune-package" {"dune-package"}
"_build/install/default/lib/rec/opam" {"opam"}
"_build/install/default/lib/rec/META"
"_build/install/default/lib/rec/dune-package"
"_build/install/default/lib/rec/opam"
]
lib_root: [
"_build/install/default/lib/coq/user-contrib/rec_module/a/bar.vo" {"coq/user-contrib/rec_module/a/bar.vo"}
Expand Down
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/include-qualified/basic/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(alias
(name default)
(action (run ./exe/test.exe)))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.9)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(executable (name test))
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
let () =
Foolib.Foo.Bar.run ();
Foolib.Foo.A.B.run ()
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(include_subdirs qualified)

(library (name foolib))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let run () = print_endline "hello from nested module B"
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let run () = print_endline "hello from nested module bar"
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(alias
(name default)
(action (run ./exe/test.exe)))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.9)
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
let () =
Foolib.Bar.Fake.run ();
Foolib.Bar.Baz.run ()
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Fake = struct
let run () =
print_endline "defined in lib interface file"
end
module Baz = Baz
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let run () = print_endline "hello from baz"
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(include_subdirs qualified)

(library
(name foolib))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
module Bar = Bar
Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.9)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let run = print_endline
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(include_subdirs qualified)

(library
(name impl)
(implements vlib))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
val run : string -> unit
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
(include_subdirs qualified)

(library
(name vlib)
(virtual_modules bar/virt))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let x = 42
8 changes: 8 additions & 0 deletions test/blackbox-tests/test-cases/include-qualified/pp/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
(include_subdirs qualified)

(library
(name foolib)
(preprocess
(per_module
((action
(run cat %{input-file})) bar/ppme))))
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.9)
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
module Bar = Bar.Ppme
39 changes: 39 additions & 0 deletions test/blackbox-tests/test-cases/include-qualified/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
Basic test showcasing the feature. Every directory creates a new level of aliasing.
$ dune build --root basic
Entering directory 'basic'
File "lib/dune", line 1, characters 17-26:
1 | (include_subdirs qualified)
^^^^^^^^^
Error: Unknown value qualified
Hint: did you mean unqualified?
[1]

We are also allowed to write lib interface files at each level.
$ dune build --root nested-lib-interface
Entering directory 'nested-lib-interface'
File "lib/dune", line 1, characters 17-26:
1 | (include_subdirs qualified)
^^^^^^^^^
Error: Unknown value qualified
Hint: did you mean unqualified?
[1]

We can nested modules virtual
$ dune build @all --root nested-virtual
Entering directory 'nested-virtual'
File "impl/dune", line 1, characters 17-26:
1 | (include_subdirs qualified)
^^^^^^^^^
Error: Unknown value qualified
Hint: did you mean unqualified?
[1]

We can set preprocessing options for nested modules
$ dune build @all --root pp
Entering directory 'pp'
File "dune", line 1, characters 17-26:
1 | (include_subdirs qualified)
^^^^^^^^^
Error: Unknown value qualified
Hint: did you mean unqualified?
[1]

0 comments on commit 3d77298

Please sign in to comment.