Skip to content
Snippets Groups Projects
sasa.ml 5.32 KiB
Newer Older
(* Time-stamp: <modified the 10/03/2019 (at 16:18) by Erwan Jahier> *)
erwan's avatar
erwan committed

(* XXX Je pourrais utiliser Lwt pour rendre step non-bloquant, ce qui
   permettrait d'accelerer la simu sur les machines qui ont plusieurs
   coeurs

  step : action -> (string -> value) Lwt.t ;
*)

open Algo
       
let (update_env_with_init : Env.t -> Process.t list -> Algo.neighbor list list -> Env.t) =
  fun e pl neighbors ->
    let (aux: Env.t -> Process.t -> Algo.neighbor list -> Env.t) =
      fun e p nl ->
        List.fold_left
          (fun e (n,_t) -> Env.set e p.pid n (p.init nl n))
          e
          p.variables
erwan's avatar
erwan committed
    in
    List.fold_left2 aux e pl neighbors
erwan's avatar
erwan committed
    
let (get_neighors: Process.t -> Topology.neighbor list) =
  fun p ->
    let id = p.Process.pid in
    let idl = try Hashtbl.find Topology.node_succ id with Not_found -> [] in
erwan's avatar
erwan committed
    List.map
      (fun id ->
         let node =
           try Hashtbl.find Topology.node_info id with Not_found -> assert false
         in
         let algo_id = Filename.chop_suffix node.file ".cmxs" in
          {
            Topology.n_id = node.id;
            Topology.n_vars = Algo.get_vars algo_id;
          }
      )
      idl

let (dump_process: Process.t * Topology.neighbor list -> unit) =
  fun (p,nl) ->
    let pvars = StringOf.algo_vars p.variables in
    let neighbors = List.map StringOf.topology_neighbor nl in
    Printf.printf "process %s\n\tvars:%s\n\tneighors: \n\t\t%s\n" p.pid  pvars
      (String.concat "\n\t\t" neighbors)

let (update_env: Env.t -> Process.t * Algo.local_env -> Env.t) =
  fun e (p, lenv) -> 
    List.fold_left
      (fun e (n,_) -> Env.set e p.pid n (lenv n))
      e
      p.variables

open Process
open SasArg
    
erwan's avatar
erwan committed
let (to_algo_neighbor: Env.t -> Topology.neighbor -> Algo.neighbor) =
  fun e n ->
    { 
      lenv= Env.get e n.Topology.n_id;
      n_vars = n.Topology.n_vars
    }

exception Silent of int


let (print_step : int -> int -> Env.t -> Process.t list -> string -> unit) =
  fun n i e pl str ->
    if SasArg.args.rif then (
      Printf.eprintf "\n#step %s\n" (string_of_int (n-i+1)) ;
      Printf.eprintf "%s #outs " str; flush stderr;
      Printf.printf "%s\n" (StringOf.env_rif e pl);
      flush stdout
    )
    else (
      Printf.eprintf "step %s: %s %s\n" (string_of_int (n-i+1)) (StringOf.env e pl) str;
      flush stderr
erwan's avatar
erwan committed
let rec (simu: int -> int -> Process.t list ->
         (Process.t * Topology.neighbor list) list -> Env.t -> unit) =
  fun n i pl pl_n e ->
    let all = List.fold_left
        (fun acc (p,nl) ->
           let nl4algo = List.map (to_algo_neighbor e) nl in
           let lenv = Env.get e p.pid in
           let al = p.enable nl4algo lenv in
           let al = List.map (fun a -> p,nl,a) al in
           if al = [] && args.demon <> Demon.Custom then acc else al::acc)
erwan's avatar
erwan committed
        [] pl_n
    in
    if (all = []) then (
      print_step n i e pl "";
erwan's avatar
erwan committed
      raise (Silent (n-i+1))
    );
    let all = if args.demon = Demon.Custom then List.rev all else all in
    let input_string, al = Demon.f SasArg.args.rif args.demon pl all in
erwan's avatar
erwan committed

    (* Do the steps *)
    let lenv_list =
      List.map (fun (p,nl,a) ->
          let nl4algo = List.map (to_algo_neighbor e) nl in
          let lenv = Env.get e p.pid in
          p, p.step nl4algo lenv a)
        al
    in
    (* update the env *)
    let ne = List.fold_left update_env e lenv_list in

    let al_str = if args.demon = Demon.Custom then
        input_string
      else 
        "("^String.concat ","
          (List.map (fun (p,_,_a) -> Printf.sprintf "%s" p.pid) al)^")"
erwan's avatar
erwan committed
    in
    print_step n i e pl al_str;
erwan's avatar
erwan committed
    match all with
erwan's avatar
erwan committed
    | [] -> assert false
    | _ ->  if i > 0 then simu n (i-1) pl pl_n ne else (
        if SasArg.args.rif then (
          print_string "q\n"; flush stdout
        ))
erwan's avatar
erwan committed

let () =
  ( try SasArg.parse Sys.argv;
	 with
	     Failure(e) ->
	       output_string stdout e;
	       flush stdout ;
	       exit 2
	   | e ->
	     output_string stdout (Printexc.to_string e);
	     flush stdout;
	     exit 2
  );


  let dot_file = SasArg.args.topo in
erwan's avatar
erwan committed
  let nl = Topology.read dot_file in
  let nstrl = List.map (fun n -> n.Topology.id) nl in
  let nstr = String.concat "," nstrl in
  try
    Algo.verbose_level := SasArg.args.verbose;
erwan's avatar
erwan committed
    Random.self_init();
    if !Algo.verbose_level > 0 then Printf.printf "nodes: %s\nedges:\n" nstr;
erwan's avatar
erwan committed
    let e = Env.init () in
    let pl = List.map Process.make nl in
erwan's avatar
erwan committed
    let neighors = List.map get_neighors pl in
    let algo_neighors = List.map (List.map (to_algo_neighbor e)) neighors in
    let e = update_env_with_init e pl algo_neighors in
erwan's avatar
erwan committed
    let pl_n = List.combine pl neighors in
    if !Algo.verbose_level > 0 then List.iter dump_process pl_n;
    let n = SasArg.args.length in
    let pl = List.rev pl in
    if SasArg.args.rif then (
      Printf.printf "#inputs %s\n" 
      (if SasArg.args.demon = Demon.Custom then (
         String.concat " " (List.map (fun p -> "\""^p.pid ^ "\":bool") pl)
      ) else "");
      Printf.printf "#outputs %s\n" (StringOf.env_rif_decl pl);
erwan's avatar
erwan committed
    simu n n pl pl_n e
  with
  | Dynlink.Error e -> Printf.printf "E: %s\n"(Dynlink.error_message e)
  | Silent i ->
    let str = if SasArg.args.rif then "#" else "" in
     Printf.printf "%sThis algo is silent after %i steps\n" str i ;
    flush stdout;
    if SasArg.args.rif then (
      print_string "q\n"; flush stdout
    )