]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/matita/matitaMathView.ml
debian: rebuilt against ocaml 3.08.3
[helm.git] / helm / matita / matitaMathView.ml
index b83c9b37fa9abe3c21fc28bdae1b266581e021b7..59324f1a1fe04e9de6e348f72f638cb3e194fb92 100644 (file)
@@ -44,121 +44,125 @@ let list_map_fail f =
  in
   aux
 
-class proof_viewer obj =
- object(self)
-
-  inherit GMathViewAux.single_selection_math_view obj
+class clickable_math_view obj =
+  let href = Gdome.domString "href" in
+  let xref = Gdome.domString "xref" in
+  object (self)
+    inherit GMathViewAux.multi_selection_math_view obj
 
-  val mutable current_infos = None
-  val mutable current_mathml = None
+    val mutable href_callback: (string -> unit) option = None
+    method set_href_callback f = href_callback <- f
 
-  initializer
-    ignore (self#connect#click (fun (gdome_elt, _, _, _) ->
+    initializer
+      ignore (self#connect#selection_changed self#choose_selection);
+      ignore (self#connect#click (fun (gdome_elt, _, _, _) ->
+        match gdome_elt with
+        | Some elt  (* element is an hyperlink, use href_callback on it *)
+          when elt#hasAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href ->
+            (match href_callback with
+            | None -> ()
+            | Some f ->
+                let uri =
+                  elt#getAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href
+                in
+                f (uri#to_string))
+        | Some elt -> ignore (self#action_toggle elt)
+        | None -> ()))
+    method private choose_selection gdome_elt =
+      let rec aux elt =
+        if elt#hasAttributeNS ~namespaceURI:Misc.helm_ns ~localName:xref then
+          self#set_selection (Some elt)
+        else
+          try
+            (match elt#get_parentNode with
+            | None -> assert false
+            | Some p -> aux (new Gdome.element_of_node p))
+          with GdomeInit.DOMCastException _ -> ()
+(*             debug_print "trying to select above the document root" *)
+      in
       match gdome_elt with
-      | Some gdome_elt ->
-          prerr_endline (gdome_elt#get_nodeName#to_string);
-          ignore (self#action_toggle gdome_elt)
-      | None -> ()));
-      (* bugfix: until mapping gtkmathview doesn't draw anything *)
-    ignore (self#misc#connect#after#map (fun _ ->
-      match current_mathml with
-      | None -> ()
-      | Some mathml -> self#load_root ~root:mathml#get_documentElement))
-
-  method load_proof ((uri_opt, _, _, _) as proof, (goal_opt: int option)) =
-    let (annobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
-        ids_to_inner_types, ids_to_conjectures, ids_to_hypotheses) =
-      Cic2acic.acic_object_of_cic_object (cicCurrentProof proof)
-    in
-    current_infos <- Some (ids_to_terms, ids_to_father_ids, ids_to_conjectures,
-      ids_to_hypotheses);
-    let mathml =
-      ApplyTransformation.mml_of_cic_object ~explode_all:true
-        (unopt_uri uri_opt) annobj ids_to_inner_sorts ids_to_inner_types
-    in
-    debug_print "load_proof: dumping MathML to /tmp/proof";
-    ignore (Misc.domImpl#saveDocumentToFile ~name:"/tmp/proof" ~doc:mathml ());
-    match current_mathml with
-    |  None ->
-        self#load_root ~root:mathml#get_documentElement ;
-        current_mathml <- Some mathml
-    | Some current_mathml ->
-        self#freeze;
-        XmlDiff.update_dom ~from:current_mathml mathml ;
-        self#thaw
+      | Some elt -> aux elt
+      | None   -> self#set_selection None
   end
 
+let clickable_math_view ?hadjustment ?vadjustment ?font_size ?log_verbosity =
+  GtkBase.Widget.size_params
+    ~cont:(OgtkMathViewProps.pack_return (fun p ->
+      OgtkMathViewProps.set_params
+        (new clickable_math_view (GtkMathViewProps.MathView_GMetaDOM.create p))
+        ~font_size:None ~log_verbosity:None))
+    []
+
 class sequent_viewer obj =
- object(self)
-
-  inherit GMathViewAux.multi_selection_math_view obj
-
-  val mutable current_infos = None
-
-  method get_selected_terms =
-   let selections = self#get_selections in
-    list_map_fail
-     (function node ->
-       let xpath =
-        ((node : Gdome.element)#getAttributeNS
-          ~namespaceURI:Misc.helmns
-          ~localName:(Gdome.domString "xref"))#to_string
-       in
-        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
-        else
-         match current_infos with
-            Some (ids_to_terms,_,_) ->
-             let id = xpath in
-              (try
-                Hashtbl.find ids_to_terms id
-               with _ -> raise Skip)
-          | None -> assert false (* "ERROR: No current term!!!" *)
-     ) selections
-
-  method get_selected_hypotheses =
-   let selections = self#get_selections in
-    list_map_fail
-     (function node ->
-       let xpath =
-        ((node : Gdome.element)#getAttributeNS
-          ~namespaceURI:Misc.helmns
-          ~localName:(Gdome.domString "xref"))#to_string
-       in
-        if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
-        else
-         match current_infos with
-            Some (_,_,ids_to_hypotheses) ->
-             let id = xpath in
-              (try
-                Hashtbl.find ids_to_hypotheses id
-               with _ -> raise Skip)
-          | None -> assert false (* "ERROR: No current term!!!" *)
-     ) selections
+  object(self)
+
+    inherit clickable_math_view obj
+
+    val mutable current_infos = None
+
+    method get_selected_terms =
+      let selections = self#get_selections in
+      list_map_fail
+        (fun node ->
+          let xpath =
+            ((node : Gdome.element)#getAttributeNS
+              ~namespaceURI:Misc.helm_ns
+              ~localName:(Gdome.domString "xref"))#to_string
+          in
+          if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+          else
+            match current_infos with
+            | Some (ids_to_terms,_,_) ->
+                (try
+                  Hashtbl.find ids_to_terms xpath
+                 with _ -> raise Skip)
+            | None -> assert false) (* "ERROR: No current term!!!" *)
+        selections
+
+    method get_selected_hypotheses =
+      let selections = self#get_selections in
+      list_map_fail
+        (fun node ->
+          let xpath =
+            ((node : Gdome.element)#getAttributeNS
+              ~namespaceURI:Misc.helm_ns
+              ~localName:(Gdome.domString "xref"))#to_string
+          in
+          if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+          else
+            match current_infos with
+            | Some (_,_,ids_to_hypotheses) ->
+                (try
+                  Hashtbl.find ids_to_hypotheses xpath
+                with _ -> raise Skip)
+            | None -> assert false) (* "ERROR: No current term!!!" *)
+        selections
   
   method load_sequent metasenv metano =
-(*
-    let (annconjecture, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
-        ids_to_hypotheses) =
-      Cic2acic.asequent_of_sequent metasenv conjecture
-    in
-*)
     let sequent = CicUtil.lookup_meta metano metasenv in
-    let (mathml, (ids_to_terms, ids_to_father_ids, ids_to_hypotheses)) =
+    let (mathml,(_,(ids_to_terms, ids_to_father_ids, ids_to_hypotheses,_))) =
       ApplyTransformation.mml_of_cic_sequent metasenv sequent
     in
     current_infos <- Some (ids_to_terms, ids_to_father_ids, ids_to_hypotheses);
-    debug_print "load_sequent: dumping MathML to /tmp/prova";
-    ignore (Misc.domImpl#saveDocumentToFile ~name:"/tmp/prova" ~doc:mathml ());
+(*
+    debug_print "load_sequent: dumping MathML to ./prova";
+    ignore (Misc.domImpl#saveDocumentToFile ~name:"./prova" ~doc:mathml ());
+*)
     self#load_root ~root:mathml#get_documentElement
  end
 
 
 class sequents_viewer ~(notebook:GPack.notebook)
-  ~(sequent_viewer:MatitaTypes.sequent_viewer) ~set_goal ()
+  ~(sequent_viewer:sequent_viewer) ()
 =
   let tab_label metano =
     (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
   in
+  let set_goal goal =
+    let currentProof = MatitaProof.instance () in
+    assert (currentProof#onGoing ());
+    currentProof#proof#set_goal goal
+  in
   object (self)
     val mutable pages = 0
     val mutable switch_page_callback = None
@@ -166,8 +170,17 @@ class sequents_viewer ~(notebook:GPack.notebook)
     val mutable goal2page = []  (* the other way round *)
     val mutable goal2win = []   (* associative list: goal no -> scrolled win *)
     val mutable _metasenv = []
+    val mutable scrolledWin: GBin.scrolled_window option = None
+      (* scrolled window to which the sequent_viewer is currently attached *)
 
     method reset =
+      (match scrolledWin with
+      | Some w ->
+          (* removing page from the notebook will destroy all contained widget,
+          * we do not want the sequent_viewer to be destroyed as well *)
+          w#remove sequent_viewer#coerce;
+          scrolledWin <- None
+      | None -> ());
       for i = 1 to pages do notebook#remove_page 0 done;
       pages <- 0;
       page2goal <- [];
@@ -187,9 +200,10 @@ class sequents_viewer ~(notebook:GPack.notebook)
       let win metano =
         let w =
           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC
-            ~show:true ()
+            ~shadow_type:`IN ~show:true ()
         in
         let reparent () =
+          scrolledWin <- Some w;
           match sequent_viewer#misc#parent with
           | None -> w#add sequent_viewer#coerce
           | Some _ -> sequent_viewer#misc#reparent w#coerce
@@ -206,7 +220,7 @@ class sequents_viewer ~(notebook:GPack.notebook)
           notebook#append_page ~tab_label:(tab_label metano) (win metano))
         metasenv;
       switch_page_callback <-
-        Some (notebook#connect#after#switch_page ~callback:(fun page ->
+        Some (notebook#connect#switch_page ~callback:(fun page ->
           let goal =
             try
               List.assoc page page2goal
@@ -218,7 +232,8 @@ class sequents_viewer ~(notebook:GPack.notebook)
     method private render_page ~page ~goal =
       sequent_viewer#load_sequent _metasenv goal;
       try
-        List.assoc goal goal2win ()
+        List.assoc goal goal2win ();
+        sequent_viewer#set_selection None
       with Not_found -> assert false
 
     method goto_sequent goal =
@@ -234,6 +249,18 @@ class sequents_viewer ~(notebook:GPack.notebook)
 
  (** constructors *)
 
+type 'widget constructor =
+  ?hadjustment:GData.adjustment ->
+  ?vadjustment:GData.adjustment ->
+  ?font_size:int ->
+  ?log_verbosity:int ->
+  ?width:int ->
+  ?height:int ->
+  ?packing:(GObj.widget -> unit) ->
+  ?show:bool ->
+  unit ->
+    'widget
+
 let sequent_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
   GtkBase.Widget.size_params
     ~cont:(OgtkMathViewProps.pack_return (fun p ->
@@ -242,27 +269,243 @@ let sequent_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
         ~font_size ~log_verbosity))
     []
 
-let proof_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
-  GtkBase.Widget.size_params
-    ~cont:(OgtkMathViewProps.pack_return (fun p ->
-      OgtkMathViewProps.set_params
-        (new proof_viewer (GtkMathViewProps.MathView_GMetaDOM.create p))
-        ~font_size ~log_verbosity))
-    []
+let blank_uri = BuildTimeConf.blank_uri
+let current_proof_uri = BuildTimeConf.current_proof_uri
 
-let proof_viewer_instance =
-  let instance = lazy (
-    let gui = MatitaGui.instance () in
-    let frame =
-      GBin.frame ~packing:(gui#proof#scrolledProof#add_with_viewport)
-        ~show:true ()
-    in
-    proof_viewer ~show:true ~packing:(frame#add) ()
-  ) in
-  fun () -> Lazy.force instance
+exception Browser_failure of string
+
+let cicBrowsers = ref []
+
+class cicBrowser ~(history:string MatitaMisc.history) () =
+  let term_RE = Pcre.regexp "^term:(.*)" in
+  let trailing_slash_RE = Pcre.regexp "/$" in
+  let gui = MatitaGui.instance () in
+  let win = gui#newBrowserWin () in
+  let toplevel = win#toplevel in
+  let mathView = sequent_viewer ~packing:win#scrolledBrowser#add () in
+  let fail msg =
+    ignore (MatitaGtkMisc.ask_confirmation ~gui:(MatitaGui.instance ())
+      ~title:"Cic browser" ~msg ~cancel:false ());
+  in
+  let handle_error f =
+    try
+      f ()
+    with exn ->
+      fail (sprintf "Uncaught exception:\n%s" (Printexc.to_string exn))
+  in
+  let handle_error' f = fun () -> handle_error f in  (* used in callbacks *)
+  object (self)
+    initializer
+      ignore (win#browserUri#connect#activate (handle_error' (fun () ->
+        self#_loadUri win#browserUri#text)));
+      ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
+        self#_loadUri current_proof_uri)));
+      ignore (win#browserRefreshButton#connect#clicked
+        (handle_error' self#refresh));
+      ignore (win#browserBackButton#connect#clicked (handle_error' self#back));
+      ignore (win#browserForwardButton#connect#clicked
+        (handle_error' self#forward));
+      ignore (win#toplevel#event#connect#delete (fun _ ->
+        let my_id = Oo.id self in
+        cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers;
+        if !cicBrowsers = [] &&
+          Helm_registry.get "matita.mode" = "cicbrowser"
+        then
+          GMain.quit ();
+        false));
+      mathView#set_href_callback (Some (fun uri ->
+        handle_error (fun () -> self#_loadUri uri)));
+      self#_loadUri ~add_to_history:false blank_uri;
+      toplevel#show ();
+
+    val disambiguator = MatitaDisambiguator.instance ()
+    val currentProof = MatitaProof.instance ()
+
+    val mutable current_uri = ""
+    val mutable current_infos = None
+    val mutable current_mathml = None
+
+    method private back () =
+      try
+        self#_loadUri ~add_to_history:false history#previous
+      with MatitaMisc.History_failure -> ()
+
+    method private forward () =
+      try
+        self#_loadUri ~add_to_history:false history#next
+      with MatitaMisc.History_failure -> ()
+
+      (* loads a uri which can be a cic uri or an about:* uri
+      * @param uri string *)
+    method private _loadUri ?(add_to_history = true) uri =
+      try
+        if current_uri <> uri || uri = current_proof_uri then begin
+          (match uri with
+          | uri when uri = blank_uri -> self#blank ()
+          | uri when uri = current_proof_uri -> self#home ()
+          | uri when Pcre.pmatch ~rex:term_RE uri ->
+              self#loadTerm (`String (Pcre.extract ~rex:term_RE uri).(1))
+          | uri when Pcre.pmatch ~rex:trailing_slash_RE uri -> self#loadDir uri
+          | _ -> self#loadUriManagerUri (UriManager.uri_of_string uri));
+          self#setUri uri;
+          if add_to_history then history#add uri
+        end
+      with
+      | UriManager.IllFormedUri _ -> fail (sprintf "invalid uri: %s" uri)
+      | CicEnvironment.Object_not_found _ ->
+          fail (sprintf "object not found: %s" uri)
+      | Browser_failure msg -> fail msg
+
+    method loadUri uri =
+      handle_error (fun () -> self#_loadUri ~add_to_history:true uri)
+
+    method private blank () =
+      mathView#load_root (MatitaMisc.empty_mathml ())#get_documentElement
+
+    method private home () =
+      if currentProof#onGoing () then
+        self#loadObj (cicCurrentProof currentProof#proof#proof)
+      else
+        raise (Browser_failure "no on going proof")
+
+      (** loads a cic uri from the environment
+      * @param uri UriManager.uri *)
+    method private loadUriManagerUri uri =
+      let uri = UriManager.strip_xpointer uri in
+      let (obj, _) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in
+      self#loadObj obj
+
+    method private loadDir dir =
+      let mathml = MatitaMisc.empty_boxml () in
+      let content = Http_getter.ls dir in
+      let root = mathml#get_documentElement in
+      let new_box_elt name =
+        mathml#createElementNS ~namespaceURI:(Some Misc.boxml_ns)
+          ~qualifiedName:(Gdome.domString ("b:" ^ name))
+      in
+      let new_text content = mathml#createTextNode (Gdome.domString content) in
+      let b_v = new_box_elt "v" in
+      List.iter
+        (fun item ->
+          let b_text = new_box_elt "text" in
+          let uri, elt =
+            match item with
+            | Http_getter_types.Ls_section subdir ->
+                (dir ^ subdir ^ "/"), (new_text (subdir ^ "/"))
+            | Http_getter_types.Ls_object obj ->
+                (dir ^ obj.Http_getter_types.uri),
+                (new_text obj.Http_getter_types.uri)
+          in
+          b_text#setAttributeNS ~namespaceURI:(Some Misc.xlink_ns)
+            ~qualifiedName:(Gdome.domString "xlink:href")
+            ~value:(Gdome.domString uri);
+          ignore (b_v#appendChild ~newChild:(b_text :> Gdome.node));
+          ignore (b_text#appendChild ~newChild:(elt :> Gdome.node)))
+        content;
+      ignore (root#appendChild ~newChild:(b_v :> Gdome.node));
+(*       Misc.domImpl#saveDocumentToFile ~doc:mathml ~name:"pippo" (); *)
+      mathView#load_root ~root:root
+
+    method private setUri uri =
+        win#browserUri#set_text uri;
+        current_uri <- uri
+
+    method private loadObj obj =
+      let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *)
+      let (mathml, (_,(ids_to_terms, ids_to_father_ids, ids_to_conjectures,
+           ids_to_hypotheses,_,_))) =
+        ApplyTransformation.mml_of_cic_object obj
+      in
+      current_infos <- Some (ids_to_terms, ids_to_father_ids,
+        ids_to_conjectures, ids_to_hypotheses);
+      match current_mathml with
+      | Some current_mathml when use_diff ->
+          mathView#freeze;
+          XmlDiff.update_dom ~from:current_mathml mathml;
+          mathView#thaw
+      |  _ ->
+          mathView#load_root ~root:mathml#get_documentElement;
+          current_mathml <- Some mathml
+
+    method private _loadTerm s =
+      self#_loadTermAst (disambiguator#parserr#parseTerm (Stream.of_string s))
+
+    method private _loadTermAst ast =
+      let (_, metasenv, term, _) =
+        MatitaCicMisc.disambiguate ~disambiguator ~currentProof ast
+      in
+      self#_loadTermCic term metasenv
+
+    method private _loadTermCic term metasenv =
+      let (context, _) =
+        MatitaCicMisc.get_context_and_metasenv currentProof
+      in
+      let dummyno = CicMkImplicit.new_meta metasenv [] in
+      let sequent = (dummyno, context, term) in
+      mathView#load_sequent (sequent :: metasenv) dummyno
+
+    method loadTerm (src:MatitaTypes.term_source) =
+      handle_error (fun () ->
+        (match src with
+        | `Ast ast -> self#_loadTermAst ast
+        | `Cic (cic, metasenv) -> self#_loadTermCic cic metasenv
+        | `String s -> self#_loadTerm s);
+        self#setUri "check")
+
+      (** {2 methods used by constructor only} *)
+
+    method win = win
+    method history = history
+    method currentUri = current_uri
+    method refresh () =
+      if current_uri = current_proof_uri then
+      self#_loadUri ~add_to_history:false current_proof_uri
+
+  end
 
 let sequents_viewer ~(notebook:GPack.notebook)
-  ~(sequent_viewer:MatitaTypes.sequent_viewer) ~set_goal ()
+  ~(sequent_viewer:sequent_viewer) ()
 =
-  new sequents_viewer ~notebook ~sequent_viewer ~set_goal ()
+  new sequents_viewer ~notebook ~sequent_viewer ()
+
+let cicBrowser () =
+  let size = BuildTimeConf.browser_history_size in
+  let rec aux history =
+    let browser = new cicBrowser ~history () in
+    let win = browser#win in
+    ignore (win#browserNewButton#connect#clicked (fun () ->
+      let history =
+        new MatitaMisc.browser_history ~memento:history#save size ""
+      in
+      let newBrowser = aux history in
+      newBrowser#loadUri browser#currentUri));
+(*
+      (* attempt (failed) to close windows on CTRL-W ... *)
+    MatitaGtkMisc.connect_key win#browserWinEventBox#event ~modifiers:[`CONTROL]
+      GdkKeysyms._W (fun () -> win#toplevel#destroy ());
+*)
+    cicBrowsers := browser :: !cicBrowsers;
+    (browser :> MatitaTypes.cicBrowser)
+  in
+  let history = new MatitaMisc.browser_history size blank_uri in
+  aux history
+
+let refresh_all_browsers () = List.iter (fun b -> b#refresh ()) !cicBrowsers
+
+class mathViewer =
+  object
+    method checkTerm (src:MatitaTypes.term_source) =
+      (cicBrowser ())#loadTerm src
+  end
+
+let mathViewer () = new mathViewer
+
+let default_sequent_viewer () = sequent_viewer ~show:true ()
+let sequent_viewer_instance = MatitaMisc.singleton default_sequent_viewer
+
+let default_sequents_viewer () =
+  let gui = MatitaGui.instance () in
+  let sequent_viewer = sequent_viewer_instance () in
+  sequents_viewer ~notebook:gui#main#sequentsNotebook ~sequent_viewer ()
+let sequents_viewer_instance = MatitaMisc.singleton default_sequents_viewer