dune/bin/main.ml

809 lines
27 KiB
OCaml
Raw Normal View History

2017-02-21 15:09:58 +00:00
open Jbuilder
open Import
open Jbuilder_cmdliner.Cmdliner
(* Things in src/ don't depend on cmdliner to speed up the bootstrap, so we set this
reference here *)
let () = suggest_function := Jbuilder_cmdliner.Cmdliner_suggest.value
2017-02-21 15:09:58 +00:00
let (>>=) = Future.(>>=)
type common =
2017-02-27 15:04:49 +00:00
{ concurrency : int
; debug_rules : bool
2017-03-03 12:46:54 +00:00
; debug_actions : bool
2017-02-27 15:04:49 +00:00
; debug_dep_path : bool
; debug_findlib : bool
; dev_mode : bool
; verbose : bool
2017-02-27 15:04:49 +00:00
; workspace_file : string option
2017-02-28 07:32:15 +00:00
; root : string
; target_prefix : string
; only_packages : String_set.t option
2017-02-21 15:09:58 +00:00
}
2017-02-28 07:32:15 +00:00
let prefix_target common s = common.target_prefix ^ s
2017-02-21 15:09:58 +00:00
let set_common c =
Clflags.concurrency := c.concurrency;
Clflags.debug_rules := c.debug_rules;
2017-03-03 12:46:54 +00:00
Clflags.debug_actions := c.debug_actions;
2017-02-21 15:09:58 +00:00
Clflags.debug_dep_path := c.debug_dep_path;
Clflags.debug_findlib := c.debug_findlib;
2017-02-28 07:32:15 +00:00
Clflags.dev_mode := c.dev_mode;
Clflags.verbose := c.verbose;
Clflags.workspace_root := c.root;
2017-02-28 07:32:15 +00:00
if c.root <> Filename.current_dir_name then
Sys.chdir c.root
2017-02-21 15:09:58 +00:00
2017-02-27 15:04:49 +00:00
module Main = struct
include Jbuilder.Main
let setup ~log ?filter_out_optional_stanzas_with_missing_deps common =
setup
~log
?workspace_file:common.workspace_file
?only_packages:common.only_packages
?filter_out_optional_stanzas_with_missing_deps ()
2017-02-27 15:04:49 +00:00
end
2017-03-01 19:19:43 +00:00
let do_build (setup : Main.setup) targets =
Build_system.do_build_exn setup.build_system targets
2017-02-28 07:32:15 +00:00
let find_root () =
let cwd = Sys.getcwd () in
let rec loop counter ~candidates ~to_cwd dir =
let files = Sys.readdir dir |> Array.to_list |> String_set.of_list in
if String_set.mem "jbuild-workspace" files then
cont counter ~candidates:((0, dir, to_cwd) :: candidates) dir ~to_cwd
else if String_set.exists files ~f:(fun fn ->
2017-03-10 10:41:34 +00:00
String.is_prefix fn ~prefix:"jbuild-workspace") then
2017-02-28 07:32:15 +00:00
cont counter ~candidates:((1, dir, to_cwd) :: candidates) dir ~to_cwd
else
cont counter ~candidates dir ~to_cwd
and cont counter ~candidates ~to_cwd dir =
if counter > String.length cwd then
candidates
else
let parent = Filename.dirname dir in
if parent = dir then
candidates
else
let base = Filename.basename dir in
loop (counter + 1) parent ~candidates ~to_cwd:(base :: to_cwd)
in
match loop 0 ~candidates:[] ~to_cwd:[] cwd with
| [] -> (cwd, [])
| l ->
let lowest_priority =
List.fold_left l ~init:max_int ~f:(fun acc (prio, _, _) ->
min acc prio)
in
match List.find l ~f:(fun (prio, _, _) -> prio = lowest_priority) with
| None -> assert false
| Some (_, dir, to_cwd) -> (dir, to_cwd)
2017-02-21 15:09:58 +00:00
let copts_sect = "COMMON OPTIONS"
let help_secs =
[ `S copts_sect
; `P "These options are common to all commands."
; `S "MORE HELP"
; `P "Use `$(mname) $(i,COMMAND) --help' for help on a single command."
; `S "BUGS"
; `P "Check bug reports at https://github.com/janestreet/jbuilder/issues"
]
let common =
let make
concurrency
debug_rules
2017-03-03 12:46:54 +00:00
debug_actions
debug_dep_path
debug_findlib
dev_mode
verbose
workspace_file
(root, only_packages)
=
2017-02-28 07:32:15 +00:00
let root, to_cwd =
match root with
| Some dn -> (dn, [])
| None -> find_root ()
in
{ concurrency
; debug_rules
2017-03-03 12:46:54 +00:00
; debug_actions
; debug_dep_path
; debug_findlib
; dev_mode
; verbose
2017-02-27 15:04:49 +00:00
; workspace_file
2017-02-28 07:32:15 +00:00
; root
; target_prefix = String.concat ~sep:"" (List.map to_cwd ~f:(sprintf "%s/"))
; only_packages =
Option.map only_packages
~f:(fun s -> String_set.of_list (String.split s ~on:','))
}
in
2017-02-21 15:09:58 +00:00
let docs = copts_sect in
let concurrency =
2017-02-28 19:05:04 +00:00
Arg.(value
& opt int !Clflags.concurrency
& info ["j"] ~docs ~docv:"JOBS"
~doc:{|Run no more than $(i,JOBS) commands simultaneously.|}
)
in
let only_packages =
Arg.(value
& opt (some string) None
& info ["only-packages"] ~docs ~docv:"PACKAGES"
~doc:{|Ignore stanzas referring to a package that is not in $(b,PACKAGES).
$(b,PACKAGES) is a coma-separated list of package name. You need to
use this option in your $(i,<package>.opam) file if your project
contains several packages.|}
)
in
2017-02-28 19:05:04 +00:00
let drules =
Arg.(value
& flag
& info ["debug-rules"] ~docs
~doc:"Print all internal rules."
)
in
2017-03-03 12:46:54 +00:00
let dactions =
Arg.(value
& flag
& info ["debug-actions"] ~docs
~doc:"Print out internal actions."
)
in
2017-02-28 19:05:04 +00:00
let ddep_path =
Arg.(value
& flag
2017-03-01 19:28:44 +00:00
& info ["debug-dependency-path"] ~docs
2017-02-28 19:05:04 +00:00
~doc:{|In case of error, print the dependency path from
the targets on the command line to the rule that failed.
|})
in
let dfindlib =
Arg.(value
& flag
& info ["debug-findlib"] ~docs
~doc:{|Debug the findlib sub-system.|})
in
let dev =
Arg.(value
& flag
& info ["dev"] ~docs
~doc:{|Use stricter compilation flags by default.|})
in
let verbose =
Arg.(value
& flag
& info ["verbose"] ~docs
~doc:"Print detailed information about commands being run")
in
2017-02-27 15:04:49 +00:00
let workspace_file =
Arg.(value
& opt (some file) None
2017-02-28 19:05:04 +00:00
& info ["workspace"] ~docs ~docv:"FILE"
2017-02-28 07:32:15 +00:00
~doc:"Use this specific workspace file instead of looking it up.")
in
let root =
Arg.(value
& opt (some dir) None
2017-02-28 19:05:04 +00:00
& info ["root"] ~docs ~docv:"DIR"
~doc:{|Use this directory as workspace root instead of guessing it.
Note that this option doesn't change the interpretation of
targets given on the command line. It is only intended
2017-02-28 19:05:04 +00:00
for scripts.|})
2017-02-27 15:04:49 +00:00
in
let for_release = "for-release-of-packages" in
let frop =
Arg.(value
& opt (some string) None
& info ["p"; for_release] ~docs ~docv:"PACKAGES"
~doc:{|Shorthand for $(b,--root . --only-packages PACKAGE).|})
in
let root_and_only_packages =
let merge root only_packages release =
match release, root, only_packages with
| Some _, Some _, _ ->
`Error (true,
sprintf
"Cannot use %s and --root simultaneously"
for_release)
| Some _, _, Some _ ->
`Error (true,
sprintf
"Cannot use %s and --only-packages simultaneously"
for_release)
| Some pkgs, None, None ->
`Ok (Some ".", Some pkgs)
| None, _, _ ->
`Ok (root, only_packages)
in
Term.(ret (const merge
$ root
$ only_packages
$ frop))
in
2017-02-27 15:04:49 +00:00
Term.(const make
$ concurrency
$ drules
2017-03-03 12:46:54 +00:00
$ dactions
2017-02-27 15:04:49 +00:00
$ ddep_path
$ dfindlib
$ dev
$ verbose
2017-02-27 15:04:49 +00:00
$ workspace_file
$ root_and_only_packages
2017-02-27 15:04:49 +00:00
)
2017-02-21 15:09:58 +00:00
let installed_libraries =
let doc = "Print out libraries installed on the system." in
let go common na =
set_common common;
Future.Scheduler.go ~log:(Log.create ())
(Context.default () >>= fun ctx ->
2017-02-28 06:01:27 +00:00
let findlib = ctx.findlib in
if na then begin
let pkgs = Findlib.all_unavailable_packages findlib in
let longest = List.longest_map pkgs ~f:(fun na -> na.package) in
let ppf = Format.std_formatter in
List.iter pkgs ~f:(fun (na : Findlib.Package_not_available.t) ->
Format.fprintf ppf "%-*s -> %a@\n" longest na.package
Findlib.Package_not_available.explain na.reason);
Format.pp_print_flush ppf ();
Future.return ()
end else begin
let pkgs = Findlib.all_packages findlib in
let max_len = List.longest_map pkgs ~f:(fun p -> p.name) in
List.iter pkgs ~f:(fun pkg ->
let ver =
match pkg.Findlib.version with
| "" -> "n/a"
| v -> v
in
Printf.printf "%-*s (version: %s)\n" max_len pkg.name ver);
Future.return ()
end)
in
( Term.(const go
$ common
$ Arg.(value
& flag
& info ["na"; "not-available"]
~doc:"List libraries that are not available and explain why"))
, Term.info "installed-libraries" ~doc
)
2017-02-24 15:41:52 +00:00
let resolve_package_install setup pkg =
match Main.package_install_file setup pkg with
| Ok path -> path
| Error () ->
die "Unknown package %s!%s" pkg (hint pkg (String_map.keys setup.packages))
2017-02-24 12:31:01 +00:00
type target =
| File of Path.t
| Alias of Path.t * Alias.t
2017-04-25 15:22:17 +00:00
let target_hint (setup : Main.setup) path =
assert (Path.is_local path);
let sub_dir = Path.parent path in
let candidates = Build_system.all_targets setup.build_system in
let candidates =
if Path.is_in_build_dir path then
candidates
else
List.map candidates ~f:(fun path ->
match Path.extract_build_context path with
| None -> path
| Some (_, path) -> path)
in
let candidates =
(* Only suggest hints for the basename, otherwise it's slow when there are lots of
files *)
List.filter_map candidates ~f:(fun path ->
if Path.parent path = sub_dir then
Some (Path.to_string path)
else
None)
in
let candidates = String_set.of_list candidates |> String_set.elements in
hint (Path.to_string path) candidates
let resolve_targets ~log common (setup : Main.setup) user_targets =
match user_targets with
| [] -> []
| _ ->
2017-02-24 12:31:01 +00:00
let targets =
2017-02-25 02:14:32 +00:00
List.concat_map user_targets ~f:(fun s ->
2017-02-24 12:31:01 +00:00
if String.is_prefix s ~prefix:"@" then
let s = String.sub s ~pos:1 ~len:(String.length s - 1) in
2017-02-28 07:32:15 +00:00
let path = Path.relative Path.root (prefix_target common s) in
2017-02-24 12:31:01 +00:00
if Path.is_root path then
2017-03-27 22:16:16 +00:00
die "@@ on the command line must be followed by a valid alias name"
2017-02-24 12:31:01 +00:00
else
let dir = Path.parent path in
2017-02-25 01:33:37 +00:00
let name = Path.basename path in
2017-02-25 02:14:32 +00:00
[Alias (path, Alias.make ~dir name)]
else
2017-02-28 07:32:15 +00:00
let path = Path.relative Path.root (prefix_target common s) in
2017-02-25 14:01:08 +00:00
let can't_build path =
2017-04-25 15:22:17 +00:00
die "Don't know how to build %s%s" (Path.to_string path)
(target_hint setup path)
2017-02-25 14:01:08 +00:00
in
if not (Path.is_local path) then
2017-02-25 02:14:32 +00:00
[File path]
2017-02-25 14:01:08 +00:00
else if Path.is_in_build_dir path then begin
if Build_system.is_target setup.build_system path then
[File path]
else
can't_build path
end else
2017-02-25 02:14:32 +00:00
match
2017-02-25 14:01:08 +00:00
let l =
List.filter_map setup.contexts ~f:(fun ctx ->
let path = Path.append ctx.Context.build_dir path in
if Build_system.is_target setup.build_system path then
Some (File path)
else
None)
in
if Build_system.is_target setup.build_system path ||
Path.exists path then
File path :: l
else
l
2017-02-25 02:14:32 +00:00
with
2017-02-25 14:01:08 +00:00
| [] -> can't_build path
2017-02-25 02:14:32 +00:00
| l -> l
)
in
if !Clflags.verbose then begin
Log.info log "Actual targets:";
List.iter targets ~f:(function
| File path ->
Log.info log @@ "- " ^ (Path.to_string path)
| Alias (path, _) ->
Log.info log @@ "- alias " ^ (Path.to_string path));
flush stdout;
end;
2017-02-24 12:31:01 +00:00
List.map targets ~f:(function
| File path -> path
| Alias (_, alias) -> Alias.file alias)
let build_targets =
2017-03-30 16:43:36 +00:00
let doc = "Build the given targets, or all installable targets if none are given." in
2017-02-28 19:05:04 +00:00
let man =
[ `S "DESCRIPTION"
; `P {|Targets starting with a $(b,@) are interpreted as aliases.|}
; `Blocks help_secs
]
in
2017-02-23 10:23:15 +00:00
let name_ = Arg.info [] ~docv:"TARGET" in
2017-02-21 15:09:58 +00:00
let go common targets =
set_common common;
let log = Log.create () in
Future.Scheduler.go ~log
(Main.setup ~log common >>= fun setup ->
let targets = resolve_targets ~log common setup targets in
2017-03-01 19:19:43 +00:00
do_build setup targets) in
2017-02-21 15:09:58 +00:00
( Term.(const go
$ common
2017-03-30 16:43:36 +00:00
$ Arg.(value & pos_all string ["@install"] name_))
2017-02-28 19:05:04 +00:00
, Term.info "build" ~doc ~man)
2017-02-21 15:09:58 +00:00
2017-02-23 13:17:25 +00:00
let runtest =
let doc = "Run tests." in
2017-02-28 19:05:04 +00:00
let man =
[ `S "DESCRIPTION"
; `P {|This is a short-hand for calling:|}
; `Pre {| jbuilder build @runtest|}
; `Blocks help_secs
]
in
2017-02-23 13:17:25 +00:00
let name_ = Arg.info [] ~docv:"DIR" in
let go common dirs =
set_common common;
let log = Log.create () in
Future.Scheduler.go ~log
(Main.setup ~log common >>= fun setup ->
2017-02-23 13:17:25 +00:00
let targets =
List.map dirs ~f:(fun dir ->
2017-02-28 07:32:15 +00:00
let dir = Path.(relative root) (prefix_target common dir) in
2017-02-23 13:17:25 +00:00
Alias.file (Alias.runtest ~dir))
in
2017-03-01 19:19:43 +00:00
do_build setup targets) in
2017-02-23 13:17:25 +00:00
( Term.(const go
$ common
2017-02-24 15:41:52 +00:00
$ Arg.(value & pos_all string ["."] name_))
2017-02-28 19:05:04 +00:00
, Term.info "runtest" ~doc ~man)
2017-02-23 13:17:25 +00:00
let format_external_libs libs =
String_map.bindings libs
|> List.map ~f:(fun (name, kind) ->
match (kind : Build.lib_dep_kind) with
| Optional -> sprintf "- %s (optional)" name
| Required -> sprintf "- %s" name)
|> String.concat ~sep:"\n"
2017-03-01 19:19:43 +00:00
let external_lib_deps =
let doc = "Print out external libraries needed to build the given targets." in
let man =
[ `S "DESCRIPTION"
; `P {|Print out the external libraries needed to build the given targets.|}
; `P {|The output of $(b,jbuild external-lib-deps @install) should be included
in what is written in your $(i,<package>.opam) file.|}
; `Blocks help_secs
]
in
let go common only_missing targets =
set_common common;
let log = Log.create () in
Future.Scheduler.go ~log
(Main.setup ~log common ~filter_out_optional_stanzas_with_missing_deps:false
>>= fun setup ->
let targets = resolve_targets ~log common setup targets in
2017-03-01 19:19:43 +00:00
let failure =
String_map.fold ~init:false
(Build_system.all_lib_deps_by_context setup.build_system targets)
~f:(fun ~key:context_name ~data:lib_deps acc ->
let internals =
2017-05-05 10:21:46 +00:00
Jbuild_types.Stanzas.lib_names
2017-03-01 19:19:43 +00:00
(match String_map.find context_name setup.Main.stanzas with
| None -> assert false
| Some x -> x)
in
let externals =
String_map.filter lib_deps ~f:(fun name _ ->
not (String_set.mem name internals))
in
if only_missing then begin
let context =
match List.find setup.contexts ~f:(fun c -> c.name = context_name) with
| None -> assert false
| Some c -> c
in
let missing =
String_map.filter externals ~f:(fun name _ ->
2017-03-15 12:07:20 +00:00
not (Findlib.available context.findlib name ~required_by:[]))
2017-03-01 19:19:43 +00:00
in
if String_map.is_empty missing then
acc
else begin
Format.eprintf
"@{<error>Error@}: The following required libraries are missing \
in the %s context:\n\
%s\n\
Hint: try: opam install %s@."
2017-03-01 19:19:43 +00:00
context_name
(format_external_libs missing)
(String_map.bindings missing
|> List.filter_map ~f:(fun (name, kind) ->
match (kind : Build.lib_dep_kind) with
| Optional -> None
| Required -> Some (Findlib.root_package_name name))
|> String_set.of_list
|> String_set.elements
|> String.concat ~sep:" ");
2017-03-01 19:19:43 +00:00
true
end
end else begin
Printf.printf
"These are the external library dependencies in the %s context:\n\
%s\n%!"
context_name
(format_external_libs externals);
2017-03-01 19:19:43 +00:00
acc
end)
in
if failure then die "";
Future.return ())
in
( Term.(const go
$ common
$ Arg.(value
& flag
& info ["missing"]
~doc:{|Only print out missing dependencies|})
$ Arg.(non_empty
& pos_all string []
& Arg.info [] ~docv:"TARGET"))
, Term.info "external-lib-deps" ~doc ~man)
2017-05-18 23:16:48 +00:00
let rules =
let doc = "Dump internal rules." in
2017-05-18 18:05:01 +00:00
let man =
[ `S "DESCRIPTION"
2017-05-18 23:16:48 +00:00
; `P {|Dump Jbuilder internal rules for the given targets.
If no targets are given, dump all the internal rules.|}
; `P {|By default the output is a list of S-expressions,
one S-expression per rule. Each S-expression is of the form:|}
; `Pre " ((deps (<dependencies>))\n\
\ (targets (<targets>))\n\
\ (context <context-name>)\n\
\ (action <action>))"
; `P {|$(b,<context-name>) is the context is which the action is executed.
It is omitted if the action is independant from the context.|}
; `P {|$(b,<action>) is the action following the same syntax as user actions,
as described in the manual.|}
2017-05-18 18:05:01 +00:00
; `Blocks help_secs
]
in
2017-05-18 23:16:48 +00:00
let go common out recursive makefile_syntax targets =
2017-05-18 18:05:01 +00:00
set_common common;
let log = Log.create () in
Future.Scheduler.go ~log
(Main.setup ~log common ~filter_out_optional_stanzas_with_missing_deps:false
>>= fun setup ->
let targets =
match targets with
| [] -> Build_system.all_targets setup.build_system
| _ -> resolve_targets ~log common setup targets
in
2017-05-18 23:16:48 +00:00
Build_system.build_rules setup.build_system targets ~recursive >>= fun rules ->
let print oc =
2017-05-18 18:05:01 +00:00
let ppf = Format.formatter_of_out_channel oc in
2017-05-18 23:16:48 +00:00
let get_action (rule : Build_system.Rule.t) =
if Path.is_root rule.action.dir then
rule.action.action
else
Chdir (rule.action.dir, rule.action.action)
in
if makefile_syntax then begin
List.iter rules ~f:(fun (rule : Build_system.Rule.t) ->
Format.fprintf ppf "%s:%s\n\t%s\n\n"
(Path.Set.elements rule.targets
|> List.map ~f:Path.to_string
|> String.concat ~sep:" ")
(Path.Set.elements rule.deps
|> List.map ~f:(fun p -> " " ^ Path.to_string p)
|> String.concat ~sep:"")
(Action.Mini_shexp.sexp_of_t (get_action rule) |> Sexp.to_string))
end else begin
List.iter rules ~f:(fun (rule : Build_system.Rule.t) ->
let sexp =
let paths ps = Sexp.To_sexp.list Path.sexp_of_t (Path.Set.elements ps) in
Sexp.To_sexp.record (
List.concat
[ [ "deps" , paths rule.deps
; "targets", paths rule.targets ]
; (match rule.action.context with
| None -> []
| Some c -> ["context", Atom c.name])
; [ "action" , Action.Mini_shexp.sexp_of_t (get_action rule) ]
])
in
Format.fprintf ppf "%s\n" (Sexp.to_string sexp))
end;
Format.pp_print_flush ppf ();
Future.return ()
in
match out with
| None -> print stdout
| Some fn -> Io.with_file_out fn ~f:print)
2017-05-18 18:05:01 +00:00
in
( Term.(const go
$ common
2017-05-18 23:16:48 +00:00
$ Arg.(value
2017-05-18 18:05:01 +00:00
& opt (some string) None
& info ["o"] ~docv:"FILE"
2017-05-18 23:16:48 +00:00
~doc:"Output to a file instead of stdout.")
$ Arg.(value
& flag
& info ["r"; "recursive"]
~doc:"Print all rules needed to build the transitive dependencies of the given targets.")
$ Arg.(value
& flag
& info ["m"; "makefile"]
~doc:"Output the rules in Makefile syntax.")
2017-05-18 18:05:01 +00:00
$ Arg.(value
& pos_all string []
& Arg.info [] ~docv:"TARGET"))
2017-05-18 23:16:48 +00:00
, Term.info "rules" ~doc ~man)
2017-05-18 18:05:01 +00:00
let opam_installer () =
match Bin.which "opam-installer" with
2017-02-24 15:41:52 +00:00
| None ->
die "\
Sorry, you need the opam-installer tool to be able to install or
uninstall packages.
I couldn't find the opam-installer binary :-("
| Some fn -> fn
let get_prefix context ~from_command_line =
2017-02-24 15:41:52 +00:00
match from_command_line with
| Some p -> Future.return (Path.of_string p)
| None -> Context.install_prefix context
2017-02-24 15:41:52 +00:00
let install_uninstall ~what =
2017-02-26 21:30:28 +00:00
let doc =
sprintf "%s packages using opam-installer." (String.capitalize_ascii what)
in
2017-02-24 15:41:52 +00:00
let name_ = Arg.info [] ~docv:"PACKAGE" in
let go common prefix pkgs =
set_common common;
let opam_installer = opam_installer () in
let log = Log.create () in
Future.Scheduler.go ~log
(Main.setup ~log common >>= fun setup ->
let pkgs =
match pkgs with
| [] -> String_map.keys setup.packages
| l -> l
in
2017-02-24 15:41:52 +00:00
let install_files, missing_install_files =
List.concat_map pkgs ~f:(fun pkg ->
2017-02-24 15:41:52 +00:00
let fn = resolve_package_install setup pkg in
List.map setup.contexts ~f:(fun ctx ->
let fn = Path.append ctx.Context.build_dir fn in
if Path.exists fn then
Inl (ctx, fn)
else
Inr fn))
|> List.partition_map ~f:(fun x -> x)
2017-02-24 15:41:52 +00:00
in
if missing_install_files <> [] then begin
die "The following <package>.install are missing:\n\
2017-02-24 15:41:52 +00:00
%s\n\
You need to run: jbuilder build @install"
2017-02-24 15:41:52 +00:00
(String.concat ~sep:"\n"
(List.map missing_install_files
~f:(fun p -> sprintf "- %s" (Path.to_string p))))
2017-02-24 15:41:52 +00:00
end;
2017-02-25 02:38:41 +00:00
(match setup.contexts, prefix with
| _ :: _ :: _, Some _ ->
die "Cannot specify --prefix when installing into multiple contexts!"
| _ -> ());
let module CMap = Map.Make(Context) in
let install_files_by_context = CMap.of_alist_multi install_files |> CMap.bindings in
2017-02-24 15:41:52 +00:00
Future.all_unit
(List.map install_files_by_context ~f:(fun (context, install_files) ->
get_prefix context ~from_command_line:prefix >>= fun prefix ->
Future.all_unit
(List.map install_files ~f:(fun path ->
let purpose = Future.Build_job install_files in
Future.run ~purpose Strict (Path.to_string opam_installer)
[ sprintf "-%c" what.[0]
; "--prefix"
; Path.to_string prefix
; Path.to_string path
])))))
2017-02-24 15:41:52 +00:00
in
( Term.(const go
$ common
$ Arg.(value & opt (some dir) None & info ["prefix"])
$ Arg.(value & pos_all string [] name_))
, Term.info what ~doc ~man:help_secs)
let install = install_uninstall ~what:"install"
let uninstall = install_uninstall ~what:"uninstall"
2017-03-01 12:09:57 +00:00
let exec =
let doc =
"Execute a command in a similar environment as if installation was performed."
in
let man =
[ `S "DESCRIPTION"
; `P {|$(b,jbuilder exec -- COMMAND) should behave in the same way as if you do:|}
; `Pre " \\$ jbuilder install\n\
\ \\$ COMMAND"
; `P {|In particular if you run $(b,jbuilder exec ocaml), you will have access
to the libraries defined in the workspace using your usual directives
($(b,#require) for instance)|}
; `Blocks help_secs
]
in
let go common context prog args =
set_common common;
let log = Log.create () in
Future.Scheduler.go ~log
(Main.setup ~log common >>= fun setup ->
2017-03-01 12:09:57 +00:00
let context =
match List.find setup.contexts ~f:(fun c -> c.name = context) with
| Some ctx -> ctx
| None ->
Format.eprintf "@{<Error>Error@}: Context %S not found!@." context;
die ""
in
let path = Config.local_install_bin_dir ~context:context.name :: context.path in
match Bin.which ~path prog with
2017-03-01 12:09:57 +00:00
| None ->
Format.eprintf "@{<Error>Error@}: Program %S not found!@." prog;
die ""
| Some real_prog ->
let real_prog = Path.to_string real_prog in
let env = Context.env_for_exec context in
if Sys.win32 then
Future.run ~env Strict real_prog (prog :: args)
else
Unix.execve real_prog (Array.of_list (prog :: args)) env
)
in
( Term.(const go
$ common
$ Arg.(value
& opt string "default"
& info ["context"] ~docv:"CONTEXT"
~doc:{|Run the command in this build context.|}
)
$ Arg.(required
& pos 0 (some string) None (Arg.info [] ~docv:"PROG"))
$ Arg.(value
& pos_right 0 string [] (Arg.info [] ~docv:"ARGS"))
)
, Term.info "exec" ~doc ~man)
let subst =
let doc =
"Substitute watermarks in source files."
in
let man =
[ `S "DESCRIPTION"
; `P {|Substitute %%ID%% strings in source files, in a similar fashion to
what topkg does in the default configuration.|}
; `P {|If you use topkg to handle the releases of your project, then you
should add this line to the $(b,build:) instructions in your opam file:|}
; `Pre {| ["jbuilder" "subst" name] {pinned}|}
; `Blocks help_secs
]
in
let go common name =
set_common common;
Future.Scheduler.go (Watermarks.subst ?name ())
in
( Term.(const go
$ common
$ Arg.(value
& opt (some string) None
& info ["n"; "name"] ~docv:"NAME"
~doc:"Use this package name instead of detecting it.")
)
, Term.info "subst" ~doc ~man)
2017-03-01 12:09:57 +00:00
2017-02-21 15:09:58 +00:00
let all =
[ installed_libraries
2017-02-23 13:17:25 +00:00
; external_lib_deps
; build_targets
2017-02-23 13:17:25 +00:00
; runtest
2017-02-24 15:41:52 +00:00
; install
; uninstall
2017-03-01 12:09:57 +00:00
; exec
; subst
2017-05-18 23:16:48 +00:00
; rules
2017-02-23 13:17:25 +00:00
]
2017-02-21 15:09:58 +00:00
let default =
2017-02-28 19:05:04 +00:00
let doc = "composable build system for OCaml" in
( Term.(ret (const (fun _ -> `Help (`Pager, None)) $ common))
2017-05-08 16:19:27 +00:00
, Term.info "jbuilder" ~doc ~version:"%%VERSION%%"
2017-02-28 19:05:04 +00:00
~man:
[ `S "DESCRIPTION"
; `P {|Jbuilder is a build system designed for OCaml projects only. It
focuses on providing the user with a consistent experience and takes
care of most of the low-level details of OCaml compilation. All you
have to do is provide a description of your project and Jbuilder will
do the rest.
|}
; `P {|The scheme it implements is inspired from the one used inside Jane
Street and adapted to the open source world. It has matured over a
long time and is used daily by hundred of developpers, which means
that it is highly tested and productive.
|}
; `Blocks help_secs
]
)
2017-02-21 15:09:58 +00:00
let () =
2017-02-24 11:28:30 +00:00
Ansi_color.setup_err_formatter_colors ();
2017-02-21 15:09:58 +00:00
try
match Term.eval_choice default all ~catch:false with
2017-02-21 15:09:58 +00:00
| `Error _ -> exit 1
| _ -> exit 0
with exn ->
Format.eprintf "%a@?" (Main.report_error ?map_fname:None) exn;
exit 1