Skip to content

Commit

Permalink
Fix #2123 (#2124)
Browse files Browse the repository at this point in the history
Fix #2123
  • Loading branch information
rgrinberg authored May 6, 2019
2 parents d328f33 + 74d07f0 commit 9c520aa
Show file tree
Hide file tree
Showing 10 changed files with 24 additions and 7 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,8 @@ unreleased
`findlib.dynload` with Dune would have to add `(special_builtin_support
findlib_dynload)` to trigger the special behavior. (#2115, @diml)

- Fix `.install` files not being generated (#2124, fixes #2123, @rgrinberg)

1.9.2 (02/05/2019)
------------------

Expand Down
7 changes: 3 additions & 4 deletions src/file_binding.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ type ('src, 'dst) t =
}

module Expanded = struct
type nonrec t = (Loc.t * Path.t, Loc.t * Path.Local.t) t
type nonrec t = (Loc.t * Path.t, Loc.t * string) t

let src t = snd t.src
let dst t = Option.map ~f:snd t.dst
Expand All @@ -21,10 +21,9 @@ module Expanded = struct
let basename = Path.basename src in
String.drop_suffix basename ~suffix:".exe"
|> Option.value ~default:basename
|> Path.Local.of_string

let dst_path t ~dir =
Path.append_local dir (dst_basename t)
Path.relative dir (dst_basename t)
end

module Unexpanded = struct
Expand Down Expand Up @@ -54,7 +53,7 @@ module Unexpanded = struct
; dst =
let f sw =
let (loc, p) = f sw in
(loc, Path.Local.of_string p)
(loc, p)
in
Option.map ~f t.dst
}
Expand Down
2 changes: 1 addition & 1 deletion src/file_binding.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Expanded : sig
type t

val src : t -> Path.t
val dst : t -> Path.Local.t option
val dst : t -> string option

val src_loc : t -> Loc.t

Expand Down
3 changes: 1 addition & 2 deletions src/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -352,8 +352,7 @@ let get_install_entries package =
List.map files ~f:(fun fb ->
let loc = File_binding.Expanded.src_loc fb in
let src = File_binding.Expanded.src fb in
let dst = Option.map ~f:Path.Local.to_string
(File_binding.Expanded.dst fb) in
let dst = File_binding.Expanded.dst fb in
( Some loc
, Install.Entry.make section src ?dst
)))
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 @@ -627,6 +627,14 @@
test-cases/github2061
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

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

(alias
(name github24)
(deps (package dune) (source_tree test-cases/github24))
Expand Down Expand Up @@ -1505,6 +1513,7 @@
(alias github20)
(alias github2033)
(alias github2061)
(alias github2123)
(alias github24)
(alias github25)
(alias github534)
Expand Down Expand Up @@ -1675,6 +1684,7 @@
(alias github20)
(alias github2033)
(alias github2061)
(alias github2123)
(alias github24)
(alias github25)
(alias github534)
Expand Down
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/github2123/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(install
(section lib)
(files (mirage-xen.pc as ../pkgconfig/mirage-xen.pc)))
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/github2123/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.9)
Empty file.
Empty file.
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/github2123/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
$ dune build @install
$ cat foo.install | grep mirage-xen
"_build/install/default/lib/pkgconfig/mirage-xen.pc" {"../pkgconfig/mirage-xen.pc"}

0 comments on commit 9c520aa

Please sign in to comment.