2016-02-19 00:20:28 +01:00
|
|
|
open Core.Std
|
|
|
|
open Qputils
|
|
|
|
|
|
|
|
(* Environment variables :
|
|
|
|
|
|
|
|
QP_PREFIX=gdb : to run gdb (or valgrind, or whatever)
|
|
|
|
QP_TASK_DEBUG=1 : debug task server
|
|
|
|
|
|
|
|
*)
|
2014-10-10 00:26:49 +02:00
|
|
|
|
|
|
|
let print_list () =
|
|
|
|
Lazy.force Qpackage.executables
|
|
|
|
|> List.iter ~f:(fun (x,_) -> Printf.printf " * %s\n" x)
|
|
|
|
|
2016-02-19 00:20:28 +01:00
|
|
|
let () =
|
|
|
|
Random.self_init ()
|
|
|
|
|
|
|
|
let run ~master exe ezfio_file =
|
2014-10-10 00:26:49 +02:00
|
|
|
|
2016-02-19 00:20:28 +01:00
|
|
|
|
|
|
|
(** Check availability of the ports *)
|
|
|
|
let port_number =
|
|
|
|
let zmq_context =
|
|
|
|
ZMQ.Context.create ()
|
|
|
|
in
|
|
|
|
let dummy_socket =
|
|
|
|
ZMQ.Socket.create zmq_context ZMQ.Socket.rep
|
|
|
|
in
|
|
|
|
let rec try_new_port port_number =
|
|
|
|
try
|
|
|
|
List.iter [ 0;1;2;3;4 ] ~f:(fun i ->
|
|
|
|
let address =
|
|
|
|
Printf.sprintf "tcp://%s:%d" (Lazy.force TaskServer.ip_address) (port_number+i)
|
|
|
|
in
|
2016-03-04 12:11:38 +01:00
|
|
|
ZMQ.Socket.bind dummy_socket address;
|
2016-02-19 00:20:28 +01:00
|
|
|
ZMQ.Socket.unbind dummy_socket address;
|
|
|
|
);
|
|
|
|
port_number
|
|
|
|
with
|
2016-03-04 12:11:38 +01:00
|
|
|
| Unix.Unix_error _ -> try_new_port (port_number+100)
|
2016-02-19 00:20:28 +01:00
|
|
|
in
|
|
|
|
let result =
|
|
|
|
try_new_port 41279
|
|
|
|
in
|
|
|
|
ZMQ.Socket.close dummy_socket;
|
|
|
|
result
|
|
|
|
in
|
|
|
|
let time_start =
|
|
|
|
Time.now ()
|
|
|
|
in
|
2014-10-10 00:26:49 +02:00
|
|
|
|
|
|
|
if (not (Sys.file_exists_exn ezfio_file)) then
|
|
|
|
failwith ("EZFIO directory "^ezfio_file^" not found");
|
|
|
|
|
|
|
|
let executables = Lazy.force Qpackage.executables in
|
|
|
|
if (not (List.exists ~f:(fun (x,_) -> x = exe) executables)) then
|
2016-02-19 19:04:03 +01:00
|
|
|
begin
|
|
|
|
Printf.printf "\nPossible choices:\n";
|
|
|
|
List.iter executables ~f:(fun (x,_) -> Printf.printf "* %s\n%!" x);
|
|
|
|
failwith ("Executable "^exe^" not found")
|
|
|
|
end;
|
2014-10-10 00:26:49 +02:00
|
|
|
|
2015-12-07 22:03:33 +01:00
|
|
|
Printf.printf "%s\n" (Time.to_string time_start);
|
2014-10-10 00:26:49 +02:00
|
|
|
Printf.printf "===============\nQuantum Package\n===============\n\n";
|
2015-12-07 22:03:33 +01:00
|
|
|
Printf.printf "Git Commit: %s\n" Git.message;
|
|
|
|
Printf.printf "Git Date : %s\n" Git.date;
|
|
|
|
Printf.printf "Git SHA1 : %s\n" Git.sha1;
|
|
|
|
Printf.printf "\n\n%!";
|
2014-10-10 00:26:49 +02:00
|
|
|
|
2015-12-07 22:03:33 +01:00
|
|
|
|
|
|
|
(** Check input *)
|
2016-02-19 00:20:28 +01:00
|
|
|
begin
|
|
|
|
match (Sys.command ("qp_edit -c "^ezfio_file)) with
|
|
|
|
| 0 -> ()
|
|
|
|
| i -> failwith "Error: Input inconsistent\n"
|
|
|
|
end;
|
|
|
|
begin
|
|
|
|
match master with
|
|
|
|
| Some address -> Unix.putenv ~key:"QP_RUN_ADDRESS_MASTER" ~data:address
|
|
|
|
| None -> ()
|
|
|
|
end;
|
2015-12-07 22:03:33 +01:00
|
|
|
|
|
|
|
(** Start task server *)
|
|
|
|
let address =
|
|
|
|
Printf.sprintf "tcp://%s:%d" (Lazy.force TaskServer.ip_address) port_number
|
|
|
|
in
|
|
|
|
let task_thread =
|
|
|
|
let thread =
|
|
|
|
Thread.create ( fun () ->
|
|
|
|
TaskServer.run port_number )
|
|
|
|
in
|
|
|
|
thread ();
|
|
|
|
in
|
|
|
|
Unix.putenv ~key:"QP_RUN_ADDRESS" ~data:address;
|
|
|
|
|
|
|
|
(** Run executable *)
|
2016-02-19 00:20:28 +01:00
|
|
|
let prefix =
|
|
|
|
match Sys.getenv "QP_PREFIX" with
|
|
|
|
| Some x -> x^" "
|
|
|
|
| None -> ""
|
|
|
|
and exe =
|
2014-10-10 00:26:49 +02:00
|
|
|
match (List.find ~f:(fun (x,_) -> x = exe) executables) with
|
2016-02-19 00:20:28 +01:00
|
|
|
| Some (_,x) -> x^" "
|
2016-02-19 19:04:03 +01:00
|
|
|
| None -> assert false
|
2014-10-10 00:26:49 +02:00
|
|
|
in
|
2016-02-19 00:20:28 +01:00
|
|
|
match (Sys.command (prefix^exe^ezfio_file)) with
|
2014-10-10 00:26:49 +02:00
|
|
|
| 0 -> ()
|
|
|
|
| i -> Printf.printf "Program exited with code %d.\n%!" i;
|
|
|
|
;
|
|
|
|
|
2015-12-07 22:03:33 +01:00
|
|
|
TaskServer.stop ~port:port_number;
|
|
|
|
Thread.join task_thread;
|
|
|
|
|
2014-10-10 00:26:49 +02:00
|
|
|
let duration = Time.diff (Time.now()) time_start
|
|
|
|
|> Core.Span.to_string in
|
2016-02-19 00:20:28 +01:00
|
|
|
Printf.printf "Wall time : %s\n\n" duration
|
2014-10-10 00:26:49 +02:00
|
|
|
|
|
|
|
let spec =
|
|
|
|
let open Command.Spec in
|
|
|
|
empty
|
2016-02-19 00:20:28 +01:00
|
|
|
+> flag "master" (optional string)
|
|
|
|
~doc:("address Address of the master process")
|
2015-11-25 10:46:53 +01:00
|
|
|
+> anon ("executable" %: string)
|
2014-10-10 00:26:49 +02:00
|
|
|
+> anon ("ezfio_file" %: string)
|
|
|
|
;;
|
|
|
|
|
2016-02-19 00:20:28 +01:00
|
|
|
|
|
|
|
|
2014-10-10 00:26:49 +02:00
|
|
|
let () =
|
|
|
|
Command.basic
|
|
|
|
~summary: "Quantum Package command"
|
|
|
|
~readme:( fun () -> "
|
2014-10-21 23:23:37 +02:00
|
|
|
Executes a Quantum Package binary file among these:\n\n"
|
2014-10-10 00:26:49 +02:00
|
|
|
^ (Lazy.force Qpackage.executables
|
|
|
|
|> List.map ~f:(fun (x,_) -> Printf.sprintf " * %s" x )
|
|
|
|
|> String.concat ~sep:"\n"
|
|
|
|
)
|
|
|
|
)
|
|
|
|
spec
|
2016-02-19 00:20:28 +01:00
|
|
|
(fun master exe ezfio_file () ->
|
|
|
|
run ~master exe ezfio_file
|
2014-10-10 00:26:49 +02:00
|
|
|
)
|
2015-12-07 22:03:33 +01:00
|
|
|
|> Command.run ~version: Git.sha1 ~build_info: Git.message
|
2014-10-10 00:26:49 +02:00
|
|
|
|
2015-12-07 22:03:33 +01:00
|
|
|
|