]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/software/matita/matitadep.ml
severe bug found in parallel zeta
[helm.git] / helm / software / matita / matitadep.ml
index 473445fffc60c5c6fff5825631558b467277296f..af811b140741372f7e44b15c98d4764eec3e37fa 100644 (file)
 
 (* $Id$ *)
 
-open Printf
+module S = Set.Make (String)
 
 module GA = GrafiteAst 
 module U = UriManager
-                
-let obj_file_of_baseuri writable baseuri = 
-  try 
-    LibraryMisc.obj_file_of_baseuri 
-     ~must_exist:true ~baseuri ~writable 
-  with 
-  | Http_getter_types.Unresolvable_URI _ 
-  | Http_getter_types.Key_not_found _ ->  
-    LibraryMisc.obj_file_of_baseuri 
-     ~must_exist:false ~baseuri ~writable:true 
-;;
+module HR = Helm_registry
+
+let print_times msg = 
+   let times = Unix.times () in
+   let stamp = times.Unix.tms_utime +. times.Unix.tms_utime in
+   Printf.printf "TIME STAMP: %s: %f\n" msg stamp; flush stdout; stamp
+
+let fix_name f =
+   let f = 
+      if Pcre.pmatch ~pat:"^\\./" f then String.sub f 2 (String.length f - 2)
+      else f
+   in 
+   HExtlib.normalize_path f
+
+(* FG: old function left for reference *)
+let exclude excluded_files files =
+   let map file = not (List.mem (fix_name file) excluded_files) in
+   List.filter map files
+
+let generate_theory theory_file deps =
+   if theory_file = "" then deps else
+   let map (files, deps) (t, d) =
+      if t = theory_file then files, deps else
+      S.add t files, List.fold_left (fun deps dep -> S.add dep deps) deps d
+   in
+   let out_include och dep = 
+      Printf.fprintf och "include \"%s\".\n\n" dep  
+   in
+   let fileset, depset = List.fold_left map (S.empty, S.empty) deps in
+   let top_depset = S.diff fileset depset in
+   let och = open_out theory_file in
+   begin
+      MatitaMisc.out_preamble och;
+      S.iter (out_include och) top_depset; 
+      close_out och;
+      (theory_file, S.elements top_depset) :: deps
+   end
 
 let main () =
+(*  let _ = print_times "inizio" in *)
+  let include_paths = ref [] in
+  let use_stdout = ref false in
+  let theory_file = ref "" in
   (* all are maps from "file" to "something" *)
-  let include_deps = Hashtbl.create (Array.length Sys.argv) in
-  let include_deps_dot = Hashtbl.create (Array.length Sys.argv) in
-  let baseuri_of = Hashtbl.create (Array.length Sys.argv) in
-  let baseuri_of_inv = Hashtbl.create (Array.length Sys.argv) in
-  let uri_deps = Hashtbl.create (Array.length Sys.argv) in
-  let ma_topo = Hashtbl.create (Array.length Sys.argv) in
-  let ma_topo_keys = ref [] in
+  let include_deps = Hashtbl.create 13 in
+  let baseuri_of = Hashtbl.create 13 in
+  let baseuri_of_inv = Hashtbl.create 13 in
+  let dot_name = "depends" in 
+  let dot_file = ref "" in
+  let set_dot_file () = dot_file := dot_name^".dot" in
+  let set_theory_file s = theory_file := s ^ ".ma" in
+  (* helpers *)
+  let rec baseuri_of_script s = 
+     try Hashtbl.find baseuri_of s 
+     with Not_found -> 
+       let _,b,_,_ =  
+         Librarian.baseuri_of_script ~include_paths:!include_paths s 
+       in
+       Hashtbl.add baseuri_of s b; 
+       Hashtbl.add baseuri_of_inv b s; 
+       let _ =
+          if Filename.check_suffix s ".mma" then
+            let generated = Filename.chop_suffix s ".mma" ^ ".ma" in
+            ignore (baseuri_of_script generated)
+       in
+       b
+  in
+  let script_of_baseuri ma b =
+    try Some (Hashtbl.find baseuri_of_inv b)
+    with Not_found -> 
+      HLog.error ("Skipping dependency of '"^ma^"' over '"^b^"'");
+      HLog.error ("Please include the file defining such baseuri, or fix");
+      HLog.error ("possibly incorrect verbatim URIs in the .ma file.");
+      None
+  in
   let buri alias = U.buri_of_uri (U.uri_of_string alias) in
   let resolve alias current_buri =
     let buri = buri alias in
-    if buri <> current_buri then Some buri else None in
-  let dot_file = ref "" in
-  let order_only = ref false in
+    if buri <> current_buri then Some buri else None 
+  in
+  (* initialization *)
   MatitaInit.add_cmdline_spec 
-    ["-dot", Arg.Set_string dot_file,
-      "<file> Save dependency graph in dot format to the given file";
-     "-order", Arg.Set order_only,
-      "Only print (one of the possibles) build order(s) for the given *.ma"];
+    ["-dot", Arg.Unit set_dot_file,
+        "Save dependency graph in dot format and generate a png";
+     "-stdout", Arg.Set use_stdout,
+        "Print dependences on stdout";
+     "-theory <name>", Arg.String set_theory_file,
+        "generate a theory file <name>.ma (it includes all other files)"
+    ];
   MatitaInit.parse_cmdline_and_configuration_file ();
   MatitaInit.initialize_environment ();
-  MatitamakeLib.initialize ();
-  let include_paths =
-   Helm_registry.get_list Helm_registry.string "matita.includes" in
-  let args = Helm_registry.get_list Helm_registry.string "matita.args" in
-  if args = [] then
-    begin
-      prerr_endline "At least one .ma file must be specified";
-      exit 1
-    end;
-  let ma_files = args in
-  let bof = Hashtbl.create 10 in
-  let baseuri_of_script s = 
-     try Hashtbl.find bof s 
-     with Not_found -> 
-       let b,_ = DependenciesParser.baseuri_of_script ~include_paths s in
-       Hashtbl.add bof s b; b
+  if not (Helm_registry.get_bool "matita.verbose") then MatitaMisc.shutup ();
+  let cmdline_args = HR.get_list HR.string "matita.args" in
+  let test x =
+     Filename.check_suffix x ".ma" || Filename.check_suffix x ".mma"
+  in
+  let files = fun () -> match cmdline_args with
+     | [] -> HExtlib.find ~test "."
+     | _  -> cmdline_args
   in
+  let args = 
+      let roots = Librarian.find_roots_in_dir (Sys.getcwd ()) in
+      match roots with
+      | [] -> 
+         prerr_endline ("No roots found in " ^ Sys.getcwd ());
+         exit 1
+      | [x] -> 
+         Sys.chdir (Filename.dirname x);
+         let opts = Librarian.load_root_file "root" in
+         include_paths := 
+           (try Str.split (Str.regexp " ") (List.assoc "include_paths" opts)
+           with Not_found -> []) @ 
+           (HR.get_list HR.string "matita.includes");
+         files ()
+      | _ ->
+         let roots = List.map (HExtlib.chop_prefix (Sys.getcwd()^"/")) roots in
+         prerr_endline ("Too many roots found:\n\t"^String.concat "\n\t" roots);
+         prerr_endline ("\nEnter one of these directories and retry");
+         exit 1
+  in
+  let ma_files = args in
+  (* here we go *)
+  (* fills:
+              Hashtbl.add include_deps     ma_file ma_file
+              Hashtbl.add include_deps_dot ma_file baseuri
+  *)
+(*  let _ = print_times "prima di iter1" in *)
+  List.iter (fun ma_file -> ignore (baseuri_of_script ma_file)) ma_files;
+(*  let _ = print_times "in mezzo alle due iter" in *)
+  let map s _ l = s :: l in
+  let ma_files = Hashtbl.fold map baseuri_of [] in
   List.iter
    (fun ma_file -> 
-    let ic = open_in ma_file in
-      let istream = Ulexing.from_utf8_channel ic in
-      let dependencies = DependenciesParser.parse_dependencies istream in
-    close_in ic;
-    if !order_only then begin
-      let relative_ma_file =
-        (* change a path leading to a .ma file into a path relative to its
-         * development root dir *)
-        let absolute_ma_file =
-          if Filename.is_relative ma_file then
-            Filename.concat (Sys.getcwd ()) ma_file
-          else
-            ma_file in
-        let ma_dir = Filename.dirname absolute_ma_file in
-        match MatitamakeLib.development_for_dir ma_dir with
-        | None ->
-            eprintf "no development setup for dir '%s'\n%!" ma_dir;
-            assert false
-        | Some devel ->
-            Pcre.replace
-              ~pat:(Pcre.quote(MatitamakeLib.root_for_development devel) ^ "/?")
-              ~templ:"" absolute_ma_file
+      let _ = if Filename.check_suffix ma_file ".mma" then
+         let generated = Filename.chop_suffix ma_file ".mma" ^ ".ma" in
+         Hashtbl.add include_deps generated ma_file;
+      in
+      let ma_baseuri = baseuri_of_script ma_file in
+      let dependencies = 
+         try DependenciesParser.deps_of_file ma_file
+        with Sys_error _ -> []
+      in
+      let handle_uri uri =
+         if not (Http_getter_storage.is_legacy uri) then
+         let dep = resolve uri ma_baseuri in
+         match dep with 
+            | None   -> ()
+            | Some u -> 
+                 match script_of_baseuri ma_file u with
+                      | Some d -> Hashtbl.add include_deps ma_file d
+                      | None   -> ()
+      in
+      let handle_script path =
+         ignore (baseuri_of_script path);
+         Hashtbl.add include_deps ma_file path
       in
-      ma_topo_keys := relative_ma_file :: !ma_topo_keys;
-      List.iter
-        (function
-          | DependenciesParser.IncludeDep path ->
-              Hashtbl.add ma_topo relative_ma_file path
-          | _ -> ())
-        dependencies
-    end else
       List.iter 
        (function
-         | DependenciesParser.UriDep uri -> 
+         | DependenciesParser.UriDep uri      ->
             let uri = UriManager.string_of_uri uri in
-            if not (Http_getter_storage.is_legacy uri) then
-              Hashtbl.add uri_deps ma_file uri
-         | DependenciesParser.BaseuriDep uri -> 
-            let uri = Http_getter_misc.strip_trailing_slash uri in
-            Hashtbl.add baseuri_of ma_file uri;
-            Hashtbl.add baseuri_of_inv uri ma_file
-         | DependenciesParser.IncludeDep path -> 
-            try 
-              let baseuri = baseuri_of_script path in
-              if not (Http_getter_storage.is_legacy baseuri) then
-                (let moo_file = obj_file_of_baseuri false baseuri in
-                Hashtbl.add include_deps ma_file moo_file;
-                Hashtbl.add include_deps_dot ma_file baseuri)
-            with Sys_error _ -> 
-              HLog.warn 
-                ("Unable to find " ^ path ^ " that is included in " ^ ma_file))
+           handle_uri uri 
+         | DependenciesParser.InlineDep path  ->
+           if Librarian.is_uri path
+           then handle_uri path else handle_script path
+        | DependenciesParser.IncludeDep path ->
+           handle_script path) 
        dependencies)
    ma_files;
-  Hashtbl.iter 
-    (fun file alias -> 
-      try 
-        let dep = resolve alias (Hashtbl.find baseuri_of file) in
-        match dep with 
-        | None -> ()
-        | Some u -> 
-           Hashtbl.add include_deps file (obj_file_of_baseuri false u)
-      with Not_found -> 
-        prerr_endline ("File "^ file^" has no baseuri. Use set baseuri");
-        exit 1)
-    uri_deps;
-      let gcp x y = 
-      (* explode and implode from the OCaml Expert FAQ. *)
-        let explode s =
-          let rec exp i l =
-            if i < 0 then l else exp (i - 1) (s.[i] :: l) in
-          exp (String.length s - 1) []
-        in      
-        let implode l =
-          let res = String.create (List.length l) in
-          let rec imp i = function
-          | [] -> res
-          | c :: l -> res.[i] <- c; imp (i + 1) l in
-          imp 0 l
-        in
-        let rec aux = function
-          | x::tl1,y::tl2 when x = y -> x::(aux (tl1,tl2))
-          | _ -> [] 
-        in
-        implode (aux (explode x,explode y))
-      in
-      let max_path = List.hd ma_files in 
-      let max_path = List.fold_left gcp max_path ma_files in
-      let short x = Pcre.replace ~pat:("^"^max_path) x in
-  if !dot_file <> "" then (* generate dependency graph if required *)
+  (* generate regular depend output *)
+(*  let _ = print_times "dopo di iter2" in *)
+  let deps =
+    List.fold_left
+     (fun acc ma_file -> 
+      let deps = Hashtbl.find_all include_deps ma_file in
+      let deps = List.fast_sort Pervasives.compare deps in
+      let deps = HExtlib.list_uniq deps in
+      let deps = List.map fix_name deps in
+      (fix_name ma_file, deps) :: acc)
+     [] ma_files
+  in
+  let extern = 
+    List.fold_left
+      (fun acc (_,d) -> 
+        List.fold_left 
+          (fun a x -> 
+             if List.exists (fun (t,_) -> x=t) deps then a 
+             else x::a) 
+          acc d)
+      [] deps
+  in
+  let where = if !use_stdout then None else Some (Sys.getcwd()) in
+  let all_deps = 
+     deps @ 
+     HExtlib.list_uniq (List.sort Pervasives.compare (List.map (fun x -> x,[]) extern))
+  in  
+  (* theory generation *)
+  let all_deps_and_theory = generate_theory !theory_file all_deps in 
+  (* matita depend file generation *)
+  Librarian.write_deps_file where all_deps_and_theory;
+  (* dot generation *)
+  if !dot_file <> "" then
     begin
       let oc = open_out !dot_file in
       let fmt = Format.formatter_of_out_channel oc in 
-      GraphvizPp.Dot.header (* ~graph_attrs:["rankdir","LR"] *) fmt;
+      GraphvizPp.Dot.header fmt;
       List.iter
-       (fun ma_file -> 
-        let deps = Hashtbl.find_all include_deps_dot ma_file in
-        let deps = 
-          HExtlib.filter_map 
-            (fun u -> 
-              try Some (Hashtbl.find baseuri_of_inv u) 
-              with Not_found -> None) 
-            deps 
-        in
-        let deps = List.fast_sort Pervasives.compare deps in
-        let deps = HExtlib.list_uniq deps in
-        GraphvizPp.Dot.node (short ma_file) fmt;
-        List.iter (fun dep -> GraphvizPp.Dot.edge (short ma_file) (short dep) fmt) deps)
-       ma_files;
+       (fun (ma_file,deps) -> 
+        GraphvizPp.Dot.node ma_file fmt;
+        List.iter (fun dep -> GraphvizPp.Dot.edge ma_file dep fmt) deps)
+       deps;
+      List.iter 
+        (fun x -> GraphvizPp.Dot.node ~attrs:["style","dashed"] x fmt) 
+        extern; 
       GraphvizPp.Dot.trailer fmt;
-      close_out oc
+      close_out oc;
+      ignore(Sys.command ("tred "^ !dot_file^"| dot -Tpng -o"^dot_name^".png"));
+      HLog.message ("Type 'eog "^dot_name^".png' to view the graph"); 
     end;
-  if !order_only then begin
-    let module OrdererString =
-      struct
-        type t = string
-        let compare = Pervasives.compare
-      end
-    in
-    let module Topo = HTopoSort.Make (OrdererString) in
-    let sorted_ma =
-      Topo.topological_sort !ma_topo_keys (Hashtbl.find_all ma_topo) in
-    List.iter print_endline sorted_ma
-    (*Hashtbl.iter (fun k v -> printf "%s: %s\n" k v) ma_topo*)
-  end else
-    List.iter (* generate regular .depend output *)
-     (fun ma_file -> 
-       try
-        let deps = Hashtbl.find_all include_deps ma_file in
-        let deps = List.fast_sort Pervasives.compare deps in
-        let deps = HExtlib.list_uniq deps in
-        let deps = ma_file :: deps in
-        let baseuri = Hashtbl.find baseuri_of ma_file in
-        let moo = obj_file_of_baseuri true baseuri in
-        printf "%s: %s\n%s: %s\n%s: %s\n%s: %s\n" 
-          moo (String.concat " " deps)
-          (Filename.basename(Pcre.replace ~pat:"ma$" ~templ:"mo" ma_file)) moo
-          (Pcre.replace ~pat:"ma$" ~templ:"mo" ma_file) moo
-          (Pcre.replace ~pat:"ma$" ~templ:"mo" (short ma_file)) moo
-       with Not_found -> 
-         prerr_endline ("File "^ma_file^" has no baseuri. Use set baseuri");
-         exit 1)
-      ma_files
-
+(*    let _ = print_times "fine" in () *)