]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/matita/matitaMathView.ml
checked in new version of matita from svn
[helm.git] / helm / matita / matitaMathView.ml
index 03803c2b94073eb3e5a72517fcda403e6b36516e..addf9763cc2350125be11b57792f8d41d1a5f506 100644 (file)
@@ -1,4 +1,4 @@
-(* Copyright (C) 2000-2002, HELM Team.
+(* Copyright (C) 2004-2005, HELM Team.
  * 
  * This file is part of HELM, an Hypertextual, Electronic
  * Library of Mathematics, developed at the Computer Science
 
 open Printf
 
-open MatitaCicMisc
 open MatitaTypes
 
-(* List utility functions *)
-exception Skip
-
 let list_map_fail f =
- let rec aux =
-  function
-     [] -> []
-   | he::tl ->
-      try
-       let he' = f he in
-        he'::(aux tl)
-      with Skip ->
-       (aux tl)
- in
+  let rec aux = function
+    | [] -> []
+    | he::tl ->
+        try
+          let he' = f he in
+          he'::(aux tl)
+        with Exit ->
+          (aux tl)
+  in
   aux
 
-class clickable_math_view obj =
+(** inherit from this class if you want to access current script *)
+class scriptAccessor =
+object (self)
+  method private script = MatitaScript.instance ()
+end
+
+class clickableMathView obj =
   let href = Gdome.domString "href" in
   let xref = Gdome.domString "xref" in
   object (self)
     inherit GMathViewAux.multi_selection_math_view obj
 
-    val mutable href_callback: (UriManager.uri -> unit) option = None
+    val mutable href_callback: (string -> unit) option = None
     method set_href_callback f = href_callback <- f
 
     initializer
@@ -65,7 +66,7 @@ class clickable_math_view obj =
                 let uri =
                   elt#getAttributeNS ~namespaceURI:Misc.xlink_ns ~localName:href
                 in
-                f (UriManager.uri_of_string (uri#to_string)))
+                f (uri#to_string))
         | Some elt -> ignore (self#action_toggle elt)
         | None -> ()))
     method private choose_selection gdome_elt =
@@ -85,48 +86,18 @@ class clickable_math_view obj =
       | None   -> self#set_selection None
   end
 
-let clickable_math_view =
+let clickableMathView ?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))
+        (new clickableMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
         ~font_size:None ~log_verbosity:None))
     []
-let clickable_math_view () = clickable_math_view ()
-
-class proof_viewer obj =
-  object (self)
-
-    inherit clickable_math_view obj
 
-    val mutable current_infos = None
-    val mutable current_mathml = None
-
-    method load_proof ((uri_opt, _, _, _) as proof, (goal_opt: int option)) =
-      let uri = unopt_uri uri_opt in
-      let obj = cicCurrentProof proof in
-      let (mathml, (ids_to_terms, ids_to_father_ids, ids_to_conjectures,
-           ids_to_hypotheses)) =
-        ApplyTransformation.mml_of_cic_object uri obj
-      in
-      current_infos <- Some (ids_to_terms, ids_to_father_ids,
-        ids_to_conjectures, ids_to_hypotheses);
-      debug_print "load_proof: dumping MathML to ./proof";
-      ignore (Misc.domImpl#saveDocumentToFile ~name:"./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
-  end
-
-class sequent_viewer obj =
+class sequentViewer obj =
   object(self)
 
-    inherit clickable_math_view obj
+    inherit clickableMathView obj
 
     val mutable current_infos = None
 
@@ -143,9 +114,7 @@ class sequent_viewer obj =
           else
             match current_infos with
             | Some (ids_to_terms,_,_) ->
-                (try
-                  Hashtbl.find ids_to_terms xpath
-                 with _ -> raise Skip)
+                (try Hashtbl.find ids_to_terms xpath with _ -> raise Exit)
             | None -> assert false) (* "ERROR: No current term!!!" *)
         selections
 
@@ -162,70 +131,78 @@ class sequent_viewer obj =
           else
             match current_infos with
             | Some (_,_,ids_to_hypotheses) ->
-                (try
-                  Hashtbl.find ids_to_hypotheses xpath
-                with _ -> raise Skip)
+                (try Hashtbl.find ids_to_hypotheses xpath with _ -> raise Exit)
             | 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 ./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:sequent_viewer) ~set_goal ()
+class sequentsViewer ~(notebook:GPack.notebook)
+  ~(sequentViewer:sequentViewer) ()
 =
-  let tab_label metano =
-    (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
-  in
   object (self)
+    inherit scriptAccessor
+
     val mutable pages = 0
     val mutable switch_page_callback = None
     val mutable page2goal = []  (* associative list: page no -> goal no *)
     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 sequentViewer is currently attached *)
+
+    method private tab_label metano =
+      (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
 
     method reset =
+      (match scrolledWin with
+      | Some w ->
+          (* removing page from the notebook will destroy all contained widget,
+          * we do not want the sequentViewer to be destroyed as well *)
+          w#remove sequentViewer#coerce;
+          scrolledWin <- None
+      | None -> ());
       for i = 1 to pages do notebook#remove_page 0 done;
       pages <- 0;
       page2goal <- [];
       goal2page <- [];
       goal2win <- [];
       _metasenv <- [];
+      self#script#setGoal ~-1;
       (match switch_page_callback with
       | Some id ->
           GtkSignal.disconnect notebook#as_widget id;
           switch_page_callback <- None
       | None -> ())
 
-    method load_sequents metasenv =
+    method load_sequents (status: ProofEngineTypes.status) =
+      let ((_, metasenv, _, _), goal) = status in
       let sequents_no = List.length metasenv in
       _metasenv <- metasenv;
       pages <- sequents_no;
+      self#script#setGoal goal;
       let win metano =
         let w =
           GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC
             ~shadow_type:`IN ~show:true ()
         in
         let reparent () =
-          match sequent_viewer#misc#parent with
-          | None -> w#add sequent_viewer#coerce
-          | Some _ -> sequent_viewer#misc#reparent w#coerce
+          scrolledWin <- Some w;
+          match sequentViewer#misc#parent with
+          | None -> w#add sequentViewer#coerce
+          | Some _ -> sequentViewer#misc#reparent w#coerce
         in
         goal2win <- (metano, reparent) :: goal2win;
         w#coerce
@@ -236,7 +213,7 @@ class sequents_viewer ~(notebook:GPack.notebook)
           page2goal <- (!page, metano) :: page2goal;
           goal2page <- (metano, !page) :: goal2page;
           incr page;
-          notebook#append_page ~tab_label:(tab_label metano) (win metano))
+          notebook#append_page ~tab_label:(self#tab_label metano) (win metano))
         metasenv;
       switch_page_callback <-
         Some (notebook#connect#switch_page ~callback:(fun page ->
@@ -245,14 +222,14 @@ class sequents_viewer ~(notebook:GPack.notebook)
               List.assoc page page2goal
             with Not_found -> assert false
           in
-          set_goal goal;
+          self#script#setGoal goal;
           self#render_page ~page ~goal))
 
     method private render_page ~page ~goal =
-      sequent_viewer#load_sequent _metasenv goal;
+      sequentViewer#load_sequent _metasenv goal;
       try
         List.assoc goal goal2win ();
-        sequent_viewer#set_selection None
+        sequentViewer#set_selection None
       with Not_found -> assert false
 
     method goto_sequent goal =
@@ -262,78 +239,275 @@ class sequents_viewer ~(notebook:GPack.notebook)
         with Not_found -> assert false
       in
       notebook#goto_page page;
-      self#render_page page goal;
+      self#render_page page goal
 
   end
 
  (** constructors *)
 
-let sequent_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
+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 sequentViewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
   GtkBase.Widget.size_params
     ~cont:(OgtkMathViewProps.pack_return (fun p ->
       OgtkMathViewProps.set_params
-        (new sequent_viewer (GtkMathViewProps.MathView_GMetaDOM.create p))
+        (new sequentViewer (GtkMathViewProps.MathView_GMetaDOM.create p))
         ~font_size ~log_verbosity))
     []
 
-class cicBrowser =
+let blank_uri = BuildTimeConf.blank_uri
+let current_proof_uri = BuildTimeConf.current_proof_uri
+
+type term_source =
+  [ `Ast of DisambiguateTypes.term
+  | `Cic of Cic.term * Cic.metasenv
+  | `String of string
+  ]
+
+exception Browser_failure of string
+
+let cicBrowsers = ref []
+
+class type cicBrowser =
+object
+  method loadUri: string -> unit
+  method loadTerm: term_source -> unit
+end
+
+class cicBrowser_impl ~(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 = sequentViewer ~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)
-    val widget =
-      let gui = MatitaGui.instance () in
-      sequent_viewer ~show:true ~packing:gui#browser#scrolledBrowser#add ()
+    inherit scriptAccessor
 
     initializer
-      widget#set_href_callback (Some (fun uri -> self#load_uri uri))
+      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 mutable current_uri = ""
+    val mutable current_infos = None
+    val mutable current_mathml = None
 
-    method load_uri uri = ()
-  end
+    method private back () =
+      try
+        self#_loadUri ~add_to_history:false history#previous
+      with MatitaMisc.History_failure -> ()
 
-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))
-    []
+    method private forward () =
+      try
+        self#_loadUri ~add_to_history:false history#next
+      with MatitaMisc.History_failure -> ()
 
-let proof_viewer_instance =
-  let instance = lazy (
-    let gui = MatitaGui.instance () in
-    proof_viewer ~show:true ~packing:gui#proof#scrolledProof#add ()
-  ) in
-  fun () -> Lazy.force instance
-
-class mathViewer =
-  let href_callback: (UriManager.uri -> unit) option ref = ref None in
-  object
-    val check_widget =
-      lazy
-        (let gui = MatitaGui.instance () in
-        let sequent_viewer =
-          sequent_viewer ~show:true ~packing:gui#check#scrolledCheck#add ()
-        in
-        sequent_viewer#set_href_callback !href_callback;
-        sequent_viewer)
+      (* 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 self#script#onGoingProof () then
+        let ((uri, metasenv, bo, ty), _) = self#script#proofStatus in
+        let name = UriManager.name_of_uri (MatitaMisc.unopt uri) in
+        let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
+        self#loadObj obj
+      else
+        self#blank ()
+
+      (** 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 = failwith "not implemented _loadTerm"
+(* TODO  self#_loadTermAst (disambiguator#parserr#parseTerm (Stream.of_string s)) *)
 
-    method set_href_callback f = href_callback := f
+    method private _loadTermAst ast = failwith "not implemented _loadTermAst"
+(* TODO
+      let (_, metasenv, term, _) =
+        MatitaCicMisc.disambiguate ~disambiguator ~currentProof ast
+      in
+      self#_loadTermCic term metasenv
+*)
 
-    method checkTerm sequent metasenv =
-      let (metano, context, expr) = sequent in
-      let widget = Lazy.force check_widget in
-      let gui = MatitaGui.instance () in
-      gui#check#checkWin#show ();
-      gui#main#showCheckMenuItem#set_active true;
-      widget#load_sequent (sequent :: metasenv) metano
+    method private _loadTermCic term metasenv =
+      let context = self#script#proofContext in
+      let dummyno = CicMkImplicit.new_meta metasenv [] in
+      let sequent = (dummyno, context, term) in
+      mathView#load_sequent (sequent :: metasenv) dummyno
+
+    method loadTerm (src: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
 
-    method unload () = (proof_viewer_instance ())#unload
   end
 
-let sequents_viewer ~(notebook:GPack.notebook)
-  ~(sequent_viewer:sequent_viewer) ~set_goal ()
+let sequentsViewer ~(notebook:GPack.notebook)
+  ~(sequentViewer:sequentViewer) ()
 =
-  new sequents_viewer ~notebook ~sequent_viewer ~set_goal ()
+  new sequentsViewer ~notebook ~sequentViewer ()
+
+let cicBrowser () =
+  let size = BuildTimeConf.browser_history_size in
+  let rec aux history =
+    let browser = new cicBrowser_impl ~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 :> 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
 
-let mathViewer () = new mathViewer
+let default_sequentViewer () = sequentViewer ~show:true ()
+let sequentViewer_instance = MatitaMisc.singleton default_sequentViewer
 
-let cicBrowser () = new cicBrowser
+let default_sequentsViewer () =
+  let gui = MatitaGui.instance () in
+  let sequentViewer = sequentViewer_instance () in
+  sequentsViewer ~notebook:gui#main#sequentsNotebook ~sequentViewer ()
+let sequentsViewer_instance = MatitaMisc.singleton default_sequentsViewer