Skip to content

Commit

Permalink
Merge pull request #2609 from rgrinberg/install-particular-section
Browse files Browse the repository at this point in the history
Add --sections option to install/uninstall
  • Loading branch information
rgrinberg authored Sep 5, 2019
2 parents 50ffcb4 + 522c455 commit a11d423
Show file tree
Hide file tree
Showing 11 changed files with 116 additions and 7 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,10 @@
`%{lib:lib:..}` when the library does not exist. (#2597, fix #1541,
@rgrinberg)

- Add `--sections` option to `$ dune install` to install subsections of .install
files. This is useful for installing only the binaries in a workspace for
example. (#2609, fixes #2554, @rgrinberg)

1.11.3 (23/08/2019)
-------------------

Expand Down
3 changes: 1 addition & 2 deletions bin/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,7 @@ module Main = struct
let open Fiber.O in
let only_packages = Common.only_packages common in
let* memory = make_memory () in
let* workspace = scan_workspace common
in
let* workspace = scan_workspace common in
init_build_system workspace
~sandboxing_preference:(Common.config common).sandboxing_preference
?memory ?external_lib_deps_mode ?only_packages
Expand Down
40 changes: 36 additions & 4 deletions bin/install_uninstall.ml
Original file line number Diff line number Diff line change
Expand Up @@ -215,6 +215,34 @@ module File_ops_real (W : Workspace) : File_operations = struct
let mkdir_p = Path.mkdir_p
end

module Sections = struct
type t =
| All
| Only of Install.Section.Set.t

let sections_conv : Install.Section.t list Cmdliner.Arg.converter =
let all =
Install.Section.all |> Install.Section.Set.to_list
|> List.map ~f:(fun section ->
(Install.Section.to_string section, section))
in
Arg.list ~sep:',' (Arg.enum all)

let term =
let doc = "sections that should be installed" in
let open Cmdliner.Arg in
let+ sections =
value & opt (some sections_conv) None & info [ "sections" ] ~doc in
match sections with
| None -> All
| Some sections -> Only (Install.Section.Set.of_list sections)

let should_install t section =
match t with
| All -> true
| Only set -> Install.Section.Set.mem set section
end

let file_operations ~dry_run ~workspace : (module File_operations) =
if dry_run then
(module File_ops_dry_run)
Expand Down Expand Up @@ -270,7 +298,7 @@ let install_uninstall ~what =
~doc:
"Select context to install from. By default, install files from \
all defined contexts.")
in
and+ sections = Sections.term in
Common.set_common common ~targets:[];
Scheduler.go ~common (fun () ->
let open Fiber.O in
Expand Down Expand Up @@ -324,11 +352,15 @@ let install_uninstall ~what =
let entries_per_package =
List.map install_files ~f:(fun (package, install_file) ->
let entries = Install.load_install_file install_file in
let entries =
List.filter entries ~f:(fun (entry : Install.Entry.t) ->
Sections.should_install sections entry.section)
in
match
List.filter_map entries ~f:(fun entry ->
Option.some_if
(not (Path.exists (Path.build entry.src)))
entry.src)
Option.some_if
(not (Path.exists (Path.build entry.src)))
entry.src)
with
| [] -> (package, entries)
| missing_files ->
Expand Down
25 changes: 24 additions & 1 deletion src/dune/install.ml
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,25 @@ end

module Section = struct
include Section0
module Map = Map.Make (Section0)
include Comparable.Make (Section0)

let all =
Set.of_list
[ Lib
; Lib_root
; Libexec
; Libexec_root
; Bin
; Sbin
; Toplevel
; Share
; Share_root
; Etc
; Doc
; Stublibs
; Man
; Misc
]

let to_string = function
| Lib -> "lib"
Expand Down Expand Up @@ -124,6 +142,11 @@ module Section = struct
| "misc" -> Some Misc
| _ -> None

let parse_string s =
match of_string s with
| Some s -> Ok s
| None -> Error (sprintf "invalid section: %s" s)

let decode =
let open Dune_lang.Decoder in
enum
Expand Down
8 changes: 8 additions & 0 deletions src/dune/install.mli
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,14 @@ module Section : sig
| Man
| Misc

module Set : Set.S with type elt = t

val all : Set.t

val to_string : t -> string

val parse_string : string -> (t, string) Result.t

val decode : t Dune_lang.Decoder.t

(** [true] iff the executable bit should be set for files installed in this
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 @@ -993,6 +993,14 @@
test-cases/install-rule-order
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

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

(alias
(name install-with-var)
(deps (package dune) (source_tree test-cases/install-with-var))
Expand Down Expand Up @@ -1866,6 +1874,7 @@
(alias install-multiple-contexts)
(alias install-partial-package)
(alias install-rule-order)
(alias install-single-section)
(alias install-with-var)
(alias installable-dup-private-libs)
(alias intf-only)
Expand Down Expand Up @@ -2066,6 +2075,7 @@
(alias install-multiple-contexts)
(alias install-partial-package)
(alias install-rule-order)
(alias install-single-section)
(alias install-with-var)
(alias installable-dup-private-libs)
(alias intf-only)
Expand Down
7 changes: 7 additions & 0 deletions test/blackbox-tests/test-cases/install-single-section/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
(executable
(public_name foo))

(install
(section man)
(package foo)
(files mp))
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(lang dune 2.0)

(package
(name foo))
Empty file.
Empty file.
22 changes: 22 additions & 0 deletions test/blackbox-tests/test-cases/install-single-section/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
Dune supports installing a subset of the sections in the .install file. This is
particularly useful if one wants to install binaries:
$ dune build @install
$ dune install --dry-run --prefix ./ --sections bin,man
Installing bin/foo
Installing man/mp
Creating directory bin
Copying _build/install/default/bin/foo to bin/foo (executable: true)
Creating directory man
Copying _build/install/default/man/mp to man/mp (executable: false)

Now let's install with the above command with one less section:

$ dune install --dry-run --prefix ./ --sections bin
Installing bin/foo
Creating directory bin
Copying _build/install/default/bin/foo to bin/foo (executable: true)

The above command shouldn't include the man page anymore

We can specify an empty list to install nothing
$ dune install --dry-run --prefix ./ --sections ""

0 comments on commit a11d423

Please sign in to comment.