]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/matita/matitaMathView.ml
fix
[helm.git] / helm / matita / matitaMathView.ml
index 46733bf607ccee627659a50acf19b0fe88ef3d4e..75541ed9d49f93df76d54668e5c6e8502457410f 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
  * http://cs.unibo.it/helm/.
  *)
 
-(***************************************************************************)
-(*                                                                         *)
-(*                             PROJECT HELM                                *)
-(*                                                                         *)
-(*                  29/01/2003 Claudio Sacerdoti Coen                      *)
-(*                                                                         *)
-(*                                                                         *)
-(***************************************************************************)
-
 open Printf
 
 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
 
-(* End of the list utility functions *)
+let add_trailing_slash =
+  let rex = Pcre.regexp "/$" in
+  fun s ->
+    if Pcre.pmatch ~rex s then s
+    else s ^ "/"
 
-class sequent_viewer obj =
- object(self)
+let strip_blanks =
+  let rex = Pcre.regexp "^\\s*([^\\s]*)\\s*$" in
+  fun s ->
+    (Pcre.extract ~rex s).(1)
 
-  inherit GMathViewAux.multi_selection_math_view obj
+(** inherit from this class if you want to access current script *)
+class scriptAccessor =
+object (self)
+  method private script = MatitaScript.instance ()
+end
 
-  val mutable current_infos = None
+class clickableMathView obj =
+  let href = Gdome.domString "href" in
+  let xref = Gdome.domString "xref" in
+  object (self)
+    inherit GMathViewAux.multi_selection_math_view obj
 
-  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!!!" *)
+    val mutable href_callback: (string -> unit) option = None
+    method set_href_callback f = href_callback <- f
+
+    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
-         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
-  
-  method load_sequent (mml:Gdome.document)
-    (metadata:MatitaTypes.sequents_metadata) sequent_no
-  =
-    let (annconjecture, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
-        ids_to_hypotheses)
-    =
-      try
-        List.assoc sequent_no metadata
-      with Not_found -> assert false
-    in
-    current_infos <- Some (ids_to_terms, ids_to_father_ids, ids_to_hypotheses);
-    self#load_root ~root:mml#get_documentElement
- end
+          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 elt -> aux elt
+      | None   -> self#set_selection None
+  end
 
-class proof_viewer obj =
- object(self)
+let clickableMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity =
+  GtkBase.Widget.size_params
+    ~cont:(OgtkMathViewProps.pack_return (fun p ->
+      OgtkMathViewProps.set_params
+        (new clickableMathView (GtkMathViewProps.MathView_GMetaDOM.create p))
+        ~font_size:None ~log_verbosity:None))
+    []
 
-  inherit GMathViewAux.single_selection_math_view obj
+class sequentViewer obj =
+  object(self)
 
-(*   initializer self#set_log_verbosity 3 *)
+    inherit clickableMathView obj
 
-  val mutable current_infos = None
-  val mutable current_mml = None
+    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 Exit)
+            | None -> assert false) (* "ERROR: No current term!!!" *)
+        selections
 
-  method load_proof (mml:Gdome.document) (metadata:MatitaTypes.proof_metadata) =
-    let (acic, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
-        ids_to_inner_types, ids_to_conjectures, ids_to_hypotheses) =
-      metadata
+    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 Exit)
+            | None -> assert false) (* "ERROR: No current term!!!" *)
+        selections
+  
+  method load_sequent metasenv metano =
+    let sequent = CicUtil.lookup_meta metano metasenv in
+    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_conjectures,ids_to_hypotheses);
-    match current_mml with
-    |  None ->
-        MatitaTypes.debug_print "no previous MathML";
-        self#load_root ~root:mml#get_documentElement ;
-        current_mml <- Some mml
-    | Some current_mml' ->
-        MatitaTypes.debug_print "Previous MathML available: xmldiffing ...";
-        self#freeze ;
-        XmlDiff.update_dom ~from:current_mml' mml ;
-        self#thaw
-  end
+    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:MatitaTypes.sequent_viewer) ()
+class sequentsViewer ~(notebook:GPack.notebook)
+  ~(sequentViewer:sequentViewer) ()
 =
   object (self)
+    inherit scriptAccessor
+
     val mutable pages = 0
     val mutable switch_page_callback = None
-    val mutable mathmls = []
-    val mutable metadata = 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;
-      mathmls <- [];
-      metadata <- None;
       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 (metadata': MatitaTypes.sequents_metadata) =
-      metadata <- Some metadata';
-      let sequents = metadata' in
-      let sequents_no = List.length sequents in
-      debug_print (sprintf "sequents no: %d" sequents_no);
+    method load_sequents (status: ProofEngineTypes.status) =
+      let ((_, metasenv, _, _), goal) = status in
+      let sequents_no = List.length metasenv in
+      _metasenv <- metasenv;
       pages <- sequents_no;
-      let widget = sequent_viewer#coerce in
+      self#script#setGoal goal;
+      let win metano =
+        let w =
+          GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC
+            ~shadow_type:`IN ~show:true ()
+        in
+        let reparent () =
+          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
+      in
       let page = ref 0 in
       List.iter
-        (fun (metano, (asequent, _, _, ids_to_inner_sorts, _)) ->
+        (fun (metano, _, _) ->
           page2goal <- (!page, metano) :: page2goal;
           goal2page <- (metano, !page) :: goal2page;
-          let tab_label =
-            (GMisc.label ~text:(sprintf "?%d" metano) ~show:true ())#coerce
-          in
-          notebook#append_page ~tab_label widget;
-          let mathml = lazy
-            (let content_sequent = Cic2content.map_sequent asequent in 
-            let pres_sequent = 
-              Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent
-            in
-            let xmlpres = Box.document_of_box pres_sequent in
-            Xml2Gdome.document_of_xml Misc.domImpl xmlpres)
-          in
-          mathmls <- (metano, mathml) :: mathmls)
-        sequents;
-      mathmls <- List.rev mathmls;
+          incr page;
+          notebook#append_page ~tab_label:(self#tab_label metano) (win metano))
+        metasenv;
       switch_page_callback <-
-        (* TODO Zack the "#after" may probably be removed after Luca's fix for
-        * widget not loading documents before being realized *)
-        Some (notebook#connect#after#switch_page ~callback:(fun page ->
-          debug_print "switch_page callback";
-          self#render_page page))
+        Some (notebook#connect#switch_page ~callback:(fun page ->
+          let goal =
+            try
+              List.assoc page page2goal
+            with Not_found -> assert false
+          in
+          self#script#setGoal goal;
+          self#render_page ~page ~goal))
+
+    method private render_page ~page ~goal =
+      sequentViewer#load_sequent _metasenv goal;
+      try
+        List.assoc goal goal2win ();
+        sequentViewer#set_selection None
+      with Not_found -> assert false
 
     method goto_sequent goal =
       let page =
@@ -210,37 +250,399 @@ class sequents_viewer ~(notebook:GPack.notebook)
         with Not_found -> assert false
       in
       notebook#goto_page page;
-      self#render_page page
-
-    method private render_page page =
-      let metadata =
-        match metadata with Some metadata -> metadata | None -> assert false
-      in
-      let (metano, mathml) = List.nth mathmls page in
-      sequent_viewer#load_sequent (Lazy.force mathml) metadata metano
+      self#render_page page goal
 
   end
 
  (** constructors *)
 
-let sequent_viewer ?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))
-        ~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 proof_viewer ?hadjustment ?vadjustment ?font_size ?log_verbosity =
+let sequentViewer ?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))
+        (new sequentViewer (GtkMathViewProps.MathView_GMetaDOM.create p))
         ~font_size ~log_verbosity))
     []
 
-let sequents_viewer ~(notebook:GPack.notebook)
-  ~(sequent_viewer:MatitaTypes.sequent_viewer) ()
+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 load: MatitaTypes.mathViewer_entry -> unit
+  (* method loadList: string list -> MatitaTypes.mathViewer_entry-> unit *)
+  method loadInput: string -> unit
+end
+
+class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history)
+  ()
+=
+  let term_RE = Pcre.regexp "^term:(.*)" in
+  let whelp_RE = Pcre.regexp "^\\s*whelp" in
+  let uri_RE =
+    Pcre.regexp
+      "^cic:/(\\w+/)*\\w+\\.(con|ind|var)(#xpointer\\(\\d+(/\\d+)+\\))?$"
+  in
+  let dir_RE = Pcre.regexp "^cic:((/(\\w+/)*\\w+(/)?)|/|)$" in
+  let whelp_query_RE = Pcre.regexp "^\\s*whelp\\s+([^\\s]+)\\s+(.*)$" in
+  let trailing_slash_RE = Pcre.regexp "/$" in
+  let has_xpointer_RE = Pcre.regexp "#xpointer\\(\\d+/\\d+(/\\d+)?\\)$" in
+  let is_whelp txt = Pcre.pmatch ~rex:whelp_RE txt in
+  let is_uri txt = Pcre.pmatch ~rex:uri_RE txt in
+  let is_dir txt = Pcre.pmatch ~rex:dir_RE txt in
+  let gui = MatitaGui.instance () in
+  let win = gui#newBrowserWin () in
+  let queries = ["Locate";"Hint";"Match";"Elim";"Instance"] in
+  let combo,_ = GEdit.combo_box_text ~strings:queries () in
+  let activate_combo_query input q =
+    let q' = String.lowercase q in
+    let rec aux i = function
+      | [] -> failwith ("Whelp query '" ^ q ^ "' not found")
+      | h::_ when String.lowercase h = q' -> i
+      | _::tl -> aux (i+1) tl
+    in
+    combo#set_active (aux 0 queries);
+    win#queryInputText#set_text input
+  in
+  let set_whelp_query txt =
+    let query, arg = 
+      try
+        let q = Pcre.extract ~rex:whelp_query_RE txt in
+        q.(1), q.(2)
+      with Invalid_argument _ -> failwith "Malformed Whelp query"
+    in
+    activate_combo_query arg query
+  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 tags =
+    [ "dir", GdkPixbuf.from_file (MatitaMisc.image_path "matita-folder.png");
+      "obj", GdkPixbuf.from_file (MatitaMisc.image_path "matita-object.png") ]
+  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 (fun () -> f ())) in
+  object (self)
+    inherit scriptAccessor
+    
+    (* Whelp bar queries *)
+
+    initializer
+      activate_combo_query "" "locate";
+      win#whelpBarComboVbox#add combo#coerce;
+      let start_query () = 
+        let query = String.lowercase (List.nth queries combo#active) in
+        let input = win#queryInputText#text in
+        let statement = "whelp " ^ query ^ " " ^ input ^ "." in
+        (MatitaScript.instance ())#advance ~statement ()
+      in
+      ignore(win#queryInputText#connect#activate ~callback:start_query);
+      ignore(combo#connect#changed ~callback:start_query);
+      win#whelpBarImage#set_file (MatitaMisc.image_path "whelp.png");
+      win#mathOrListNotebook#set_show_tabs false;
+
+      win#browserForwardButton#misc#set_sensitive false;
+      win#browserBackButton#misc#set_sensitive false;
+      ignore (win#browserUri#entry#connect#activate (handle_error' (fun () ->
+        self#loadInput win#browserUri#entry#text)));
+      ignore (win#browserHomeButton#connect#clicked (handle_error' (fun () ->
+        self#load (`About `Current_proof))));
+      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));
+      ignore(win#whelpResultTreeview#connect#row_activated 
+        ~callback:(fun _ _ -> self#loadInput (self#_getSelectedUri ())));
+      mathView#set_href_callback (Some (fun uri ->
+        handle_error (fun () -> self#load (`Uri uri))));
+      self#_load (`About `Blank);
+      toplevel#show ()
+
+    val mutable current_entry = `About `Blank 
+    val mutable current_infos = None
+    val mutable current_mathml = None
+
+    val model =
+      new MatitaGtkMisc.taggedStringListModel tags win#whelpResultTreeview
+
+    method private _getSelectedUri () =
+      match model#easy_selection () with
+      | [sel] when is_uri sel -> sel  (* absolute URI selected *)
+      | [sel] -> win#browserUri#entry#text ^ sel  (* relative URI selected *)
+      | _ -> assert false
+
+    (** history RATIONALE 
+     *
+     * All operations about history are done using _historyFoo.
+     * Only toplevel functions (ATM load and loadInput) call _historyAdd.
+     *)
+          
+    method private _historyAdd item = 
+      history#add item;
+      win#browserBackButton#misc#set_sensitive true;
+      win#browserForwardButton#misc#set_sensitive false
+
+    method private _historyPrev () =
+      let item = history#previous in
+      if history#is_begin then win#browserBackButton#misc#set_sensitive false;
+      win#browserForwardButton#misc#set_sensitive true;
+      item
+    
+    method private _historyNext () =
+      let item = history#next in
+      if history#is_end then win#browserForwardButton#misc#set_sensitive false;
+      win#browserBackButton#misc#set_sensitive true;
+      item
+
+    (** notebook RATIONALE 
+     * 
+     * Use only these functions to switch between the tabs
+     *)
+    method private _showList = win#mathOrListNotebook#goto_page 1
+    method private _showMath = win#mathOrListNotebook#goto_page 0
+    
+    method private back () =
+      try
+        self#_load (self#_historyPrev ())
+      with MatitaMisc.History_failure -> ()
+
+    method private forward () =
+      try
+        self#_load (self#_historyNext ())
+      with MatitaMisc.History_failure -> ()
+
+      (* loads a uri which can be a cic uri or an about:* uri
+      * @param uri string *)
+    method private _load entry =
+      try
+          if entry <> current_entry || entry = `About `Current_proof then begin
+            (match entry with
+            | `About `Current_proof -> self#home ()
+            | `About `Blank -> self#blank ()
+            | `About `Us -> () (* TODO implement easter egg here :-] *)
+            | `Check term -> self#_loadCheck term
+            | `Cic (term, metasenv) -> self#_loadTermCic term metasenv
+            | `Dir dir -> self#_loadDir dir
+            | `Uri uri -> self#_loadUriManagerUri (UriManager.uri_of_string uri)
+            | `Whelp (query, results) -> 
+                set_whelp_query query;
+                self#_loadList (List.map (fun r -> "obj", r) results));
+            self#setEntry entry
+          end
+      with
+      | UriManager.IllFormedUri uri -> fail (sprintf "invalid uri: %s" uri)
+      | CicEnvironment.Object_not_found uri ->
+          fail (sprintf "object not found: %s" (UriManager.string_of_uri uri))
+      | Browser_failure msg -> fail msg
+
+    method private blank () =
+      self#_showMath;
+      mathView#load_root (MatitaMisc.empty_mathml ())#get_documentElement
+
+    method private _loadCheck term =
+      failwith "not implemented _loadCheck";
+      self#_showMath
+
+    method private home () =
+      self#_showMath;
+      match self#script#status.proof_status with
+      | Proof  (uri, metasenv, bo, ty) ->
+          let name = UriManager.name_of_uri (MatitaMisc.unopt uri) in
+          let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
+          self#_loadObj obj
+      | Incomplete_proof ((uri, metasenv, bo, ty), _) -> 
+          let name = UriManager.name_of_uri (MatitaMisc.unopt uri) in
+          let obj = Cic.CurrentProof (name, metasenv, bo, ty, [], []) in
+          self#_loadObj obj
+      | _ -> 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 content = Http_getter.ls dir in
+      let l =
+        List.map
+          (function 
+            | Http_getter_types.Ls_section s -> "dir", s
+            | Http_getter_types.Ls_object o -> "obj", o.Http_getter_types.uri)
+          content
+      in
+      if l = [] then raise (Browser_failure "no such directory");
+      self#_loadList l
+
+    method private setEntry entry =
+      win#browserUri#entry#set_text (string_of_entry entry);
+      current_entry <- entry
+
+    method private _loadObj obj =
+      self#_showMath; 
+      (* this must be _before_ loading the document, since 
+       * if the widget is not mapped (hidden by the notebook)
+       * the document is not rendered *)
+      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 _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;
+      self#_showMath
+
+    method private _loadList l =
+      model#list_store#clear ();
+      List.iter (fun (tag, s) -> model#easy_append ~tag s) l;
+      self#_showList
+    
+    (** { public methods, all must call _load!! } *)
+      
+    method load entry =
+      handle_error (fun () -> self#_load entry; self#_historyAdd entry)
+
+    (**  this is what the browser does when you enter a string an hit enter *)
+    method loadInput txt =
+      let txt = strip_blanks txt in
+      let fix_uri txt =
+        UriManager.string_of_uri
+          (UriManager.strip_xpointer (UriManager.uri_of_string txt))
+      in
+      if is_whelp txt then begin
+        set_whelp_query txt;  
+        (MatitaScript.instance ())#advance ~statement:(txt ^ ".") ()
+      end else begin
+        let entry =
+          match txt with
+          | txt when is_uri txt -> `Uri (fix_uri txt)
+          | txt when is_dir txt -> `Dir (add_trailing_slash txt)
+          | txt ->
+              (try
+                entry_of_string txt
+              with Invalid_argument _ ->
+                raise (Browser_failure (sprintf "unsupported uri: %s" txt)))
+        in
+        self#_load entry;
+        self#_historyAdd entry
+      end
+
+      (** {2 methods used by constructor only} *)
+
+    method win = win
+    method history = history
+    method currentEntry = current_entry
+    method refresh () =
+      if current_entry = `About `Current_proof then
+      self#_load (`About `Current_proof) 
+  end
+
+  
+let sequentsViewer ~(notebook:GPack.notebook)
+  ~(sequentViewer:sequentViewer) ()
 =
-  new sequents_viewer ~notebook ~sequent_viewer ()
+  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
+          (`About `Blank)
+      in
+      let newBrowser = aux history in
+      newBrowser#load browser#currentEntry));
+(*
+      (* 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 (`About `Blank) in
+  aux history
+
+let refresh_all_browsers () = List.iter (fun b -> b#refresh ()) !cicBrowsers
+
+let default_sequentViewer () = sequentViewer ~show:true ()
+let sequentViewer_instance = MatitaMisc.singleton default_sequentViewer
+
+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
+
+let mathViewer () = 
+  object(self)
+    method private get_browser reuse = 
+      if reuse then
+        (match !cicBrowsers with
+        | [] -> cicBrowser ()
+        | b :: _ -> (b :> cicBrowser))
+      else
+        (cicBrowser ())
+          
+    method show_entry ?(reuse=false) t = (self#get_browser reuse)#load t
+      
+    method show_uri_list ?(reuse=false) ~entry l =
+      (self#get_browser reuse)#load entry
+  end