diff options
-rw-r--r-- | ocamlbuild/Makefile | 10 | ||||
-rw-r--r-- | ocamlbuild/TODO | 2 | ||||
-rw-r--r-- | ocamlbuild/my_unix.mli | 2 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuild.ml | 2 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuild.mltop | 3 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuild_executor.ml (renamed from ocamlbuild/executor.ml) | 27 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuild_executor.mli (renamed from ocamlbuild/executor.mli) | 35 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuild_unix_plugin.ml (renamed from ocamlbuild/my_unix_with_unix.ml) | 11 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuild_unix_plugin.mli (renamed from ocamlbuild/my_unix_with_unix.mli) | 0 | ||||
-rw-r--r-- | ocamlbuild/ocamlbuildlib.mllib | 4 | ||||
-rw-r--r-- | ocamlbuild/signatures.mli | 2 |
11 files changed, 63 insertions, 35 deletions
diff --git a/ocamlbuild/Makefile b/ocamlbuild/Makefile index e2cb570b6..66166c34f 100644 --- a/ocamlbuild/Makefile +++ b/ocamlbuild/Makefile @@ -82,8 +82,18 @@ install: all $(BUILDDIR)/ocamlbuildlightlib.cmxa \ $(BUILDDIR)/ocamlbuildlightlib.a \ $(BUILDDIR)/ocamlbuildlightlib.cma \ + $(BUILDDIR)/ocamlbuild_unix_plugin.cmx \ + $(BUILDDIR)/ocamlbuild_unix_plugin.o \ + $(BUILDDIR)/ocamlbuild_unix_plugin.cmo \ + $(BUILDDIR)/ocamlbuild_unix_plugin.cmi \ + $(BUILDDIR)/ocamlbuild_executor.cmi \ + $(BUILDDIR)/ocamlbuild_executor.cmo \ + $(BUILDDIR)/ocamlbuild_executor.cmx \ + $(BUILDDIR)/ocamlbuild_executor.o \ $(BUILDDIR)/ocamlbuild_pack.cmi \ + $(BUILDDIR)/ocamlbuild_pack.cmo \ $(BUILDDIR)/ocamlbuild_pack.cmx \ + $(BUILDDIR)/ocamlbuild_pack.o \ $(BUILDDIR)/ocamlbuild.cmi \ $(BUILDDIR)/ocamlbuild_plugin.cmi \ $(BUILDDIR)/ocamlbuild.cmx \ diff --git a/ocamlbuild/TODO b/ocamlbuild/TODO index 442513c8a..bbc58f597 100644 --- a/ocamlbuild/TODO +++ b/ocamlbuild/TODO @@ -1,7 +1,6 @@ To do: * Add rules for producing .recdepends from .ml, .mli, .mllib, .mlpack * Produce a dependency subgraph when failing on circular deps (e.g. "A: B C\nB: D") -* Export my_unix_with_unix and executor (and change its name) * Executor: exceptional conditions and Not_found * Fix report * Design a nice, friendly, future-proof plugin (myocamlbuild) API @@ -37,3 +36,4 @@ Done: * Have some option to draw tags/rules that applies on a target (it's -show-tags). * rm sanitize.sh during -clean * rm sanitize.sh when running ocamlbuild +* Export my_unix_with_unix and executor (and change its name) diff --git a/ocamlbuild/my_unix.mli b/ocamlbuild/my_unix.mli index 5233415d4..a0e59d672 100644 --- a/ocamlbuild/my_unix.mli +++ b/ocamlbuild/my_unix.mli @@ -30,7 +30,7 @@ val run_and_open : string -> (in_channel -> 'a) -> 'a val readlink : string -> string val run_and_read : string -> string -(** See [Executor.execute] *) +(** See [Ocamlbuild_executor.execute] *) val execute_many : ?max_jobs:int -> ?ticker:(unit -> unit) -> diff --git a/ocamlbuild/ocamlbuild.ml b/ocamlbuild/ocamlbuild.ml index 96d78185b..aef74f5d1 100644 --- a/ocamlbuild/ocamlbuild.ml +++ b/ocamlbuild/ocamlbuild.ml @@ -11,5 +11,5 @@ (* $Id$ *) (* Original author: Nicolas Pouillard *) -My_unix_with_unix.setup (); +Ocamlbuild_unix_plugin.setup (); Ocamlbuild_pack.Main.main () diff --git a/ocamlbuild/ocamlbuild.mltop b/ocamlbuild/ocamlbuild.mltop index eb1598d64..41c1afb01 100644 --- a/ocamlbuild/ocamlbuild.mltop +++ b/ocamlbuild/ocamlbuild.mltop @@ -1,4 +1,3 @@ -Executor -My_unix_with_unix Ocamlbuild_pack Ocamlbuild_plugin +Ocamlbuild_unix_plugin diff --git a/ocamlbuild/executor.ml b/ocamlbuild/ocamlbuild_executor.ml index 300e1a6ae..70018eeef 100644 --- a/ocamlbuild/executor.ml +++ b/ocamlbuild/ocamlbuild_executor.ml @@ -11,16 +11,15 @@ (* $Id$ *) (* Original author: Berke Durak *) -(* Executor *) +(* Ocamlbuild_executor *) open Unix;; -module Exit_codes = struct - let rc_subcommand_failed = 10 - let rc_subcommand_got_signal = 11 - let rc_io_error = 12 - let rc_exceptional_condition = 13 -end;; +type error = + | Subcommand_failed + | Subcommand_got_signal + | Io_error + | Exceptionl_condition type task = (string * (unit -> unit));; @@ -50,11 +49,6 @@ let print_unix_status oc = function | WSTOPPED i -> fp oc "stop %d" i ;; (* ***) -(*** exit *) -let exit rc = - raise (Ocamlbuild_pack.My_std.Exit_with_code rc) -;; -(* ***) (*** print_job_id *) let print_job_id oc (x,y) = fp oc "%d.%d" x y;; (* ***) @@ -91,6 +85,7 @@ let execute ?(ticker=ignore) ?(period=0.1) ?(display=(fun f -> f Pervasives.stdout)) + ~exit (commands : task list list) = let batch_id = ref 0 in @@ -222,7 +217,7 @@ let execute fp oc "Exception %s while reading output of command %S\n%!" job.job_command (Printexc.to_string x); end; - exit Exit_codes.rc_io_error + exit Io_error in (* ***) (*** process_jobs_to_terminate *) @@ -273,12 +268,12 @@ let execute show_command (); display (fun oc -> fp oc "Command exited with code %d.\n" rc); all_ok := false; - exit Exit_codes.rc_subcommand_failed + exit Subcommand_failed | Unix.WSTOPPED s | Unix.WSIGNALED s -> show_command (); all_ok := false; display (fun oc -> fp oc "Command got signal %d.\n" s); - exit Exit_codes.rc_subcommand_got_signal + exit Subcommand_got_signal end done in @@ -318,7 +313,7 @@ let execute chxfds, begin fun _ _job -> (*display (fun oc -> fp oc "Exceptional condition on command %S\n%!" job.job_command); - exit Exit_codes.rc_exceptional_condition*) + exit Exceptional_condition*) () (* FIXME *) end]; loop () diff --git a/ocamlbuild/executor.mli b/ocamlbuild/ocamlbuild_executor.mli index 76fc6879f..e4293facf 100644 --- a/ocamlbuild/executor.mli +++ b/ocamlbuild/ocamlbuild_executor.mli @@ -11,25 +11,40 @@ (* $Id$ *) (* Original author: Berke Durak *) -(* Executor *) +(* Ocamlbuild_executor *) (** UNIX-specific module for running tasks in parallel and properly multiplexing their outputs. *) -(** [execute ~ticker ~period ~display commands] will execute the commands in [commands] - in parallel, correctly multiplexing their outputs. A command is a pair [(cmd, action)] - where [cmd] is a shell command string, and [action] is a thunk that is to be called just - before [cmd] is about to be executed. If specified, it will call [ticker] at least every [period] - seconds. If specified, it will call [display f] when it wishes to print something; - [display] should then call [f] with then channel on which [f] should print. - Note that [f] must be idempotent as it may well be called twice, once for the log file, - once for the actual output. - If one of the commands fails, it will exit with an appropriate error code, +type error = + | Subcommand_failed + | Subcommand_got_signal + | Io_error + | Exceptionl_condition + +(** [execute ~ticker ~period ~display ~exit commands] will execute the commands + in [commands] in parallel, correctly multiplexing their outputs. + + A command is a pair [(cmd, action)] where [cmd] is a shell command string, + and [action] is a thunk that is to be called just before [cmd] is about to + be executed. If specified, it will call [ticker] at least every [period] + seconds. If specified, it will call [display f] when it wishes to print + something; [display] should then call [f] with then channel on which [f] + should print. + + Note that [f] must be idempotent as it may well be called twice, once for + the log file, once for the actual output. + + If one of the commands fails, it will exit with an appropriate error code, calling [cleanup] before. + + All exits are done trough the call to the given [exit] function, if not + supplied Pervasives.exit is used. *) val execute : ?max_jobs:int -> ?ticker:(unit -> unit) -> ?period:float -> ?display:((out_channel -> unit) -> unit) -> + exit:(error -> unit) -> ((string * (unit -> unit)) list list) -> (bool list * exn) option diff --git a/ocamlbuild/my_unix_with_unix.ml b/ocamlbuild/ocamlbuild_unix_plugin.ml index 2bca1f9d5..d0dfd8dee 100644 --- a/ocamlbuild/my_unix_with_unix.ml +++ b/ocamlbuild/ocamlbuild_unix_plugin.ml @@ -59,12 +59,21 @@ let run_and_open s kont = let stdout_isatty () = Unix.isatty Unix.stdout +let execute_many = + let exit = function + | Ocamlbuild_executor.Subcommand_failed -> exit Exit_codes.rc_executor_subcommand_failed + | Ocamlbuild_executor.Subcommand_got_signal -> exit Exit_codes.rc_executor_subcommand_got_signal + | Ocamlbuild_executor.Io_error -> exit Exit_codes.rc_executor_io_error + | Ocamlbuild_executor.Exceptionl_condition -> exit Exit_codes.rc_executor_excetptional_condition + in + Ocamlbuild_executor.execute ~exit + let setup () = implem.is_degraded <- false; implem.stdout_isatty <- stdout_isatty; implem.gettimeofday <- Unix.gettimeofday; implem.report_error <- report_error; - implem.execute_many <- Executor.execute; + implem.execute_many <- execute_many; implem.readlink <- Unix.readlink; implem.run_and_open <- run_and_open; implem.at_exit_once <- at_exit_once; diff --git a/ocamlbuild/my_unix_with_unix.mli b/ocamlbuild/ocamlbuild_unix_plugin.mli index 1d87e4dee..1d87e4dee 100644 --- a/ocamlbuild/my_unix_with_unix.mli +++ b/ocamlbuild/ocamlbuild_unix_plugin.mli diff --git a/ocamlbuild/ocamlbuildlib.mllib b/ocamlbuild/ocamlbuildlib.mllib index eb1598d64..767ed32c6 100644 --- a/ocamlbuild/ocamlbuildlib.mllib +++ b/ocamlbuild/ocamlbuildlib.mllib @@ -1,4 +1,4 @@ -Executor -My_unix_with_unix Ocamlbuild_pack Ocamlbuild_plugin +Ocamlbuild_unix_plugin +Ocamlbuild_executor diff --git a/ocamlbuild/signatures.mli b/ocamlbuild/signatures.mli index 4b0164256..d69fc2481 100644 --- a/ocamlbuild/signatures.mli +++ b/ocamlbuild/signatures.mli @@ -200,7 +200,7 @@ module type COMMAND = sig val execute : ?quiet:bool -> ?pretend:bool -> t -> unit (** Run the commands in the given list, if possible in parallel. - See the module [Executor]. *) + See the module [Ocamlbuild_executor]. *) val execute_many : ?quiet:bool -> ?pretend:bool -> t list -> (bool list * exn) option (** [setup_virtual_command_solver virtual_command solver] |