X-Git-Url: http://matita.cs.unibo.it/gitweb/?a=blobdiff_plain;f=matita%2Fmatita%2FmatitaMathView.ml;h=271a7b19ab45c664f61aac4c805b435d81415044;hb=5d9f7ae4bad2b5926f615141c12942b9a8eb23fb;hp=f11354904b6296ec31f3b2bb9d3896ba5b6f0a10;hpb=d541d1b9cc3cffedf0d1903a39cd4683e1e6ef97;p=helm.git diff --git a/matita/matita/matitaMathView.ml b/matita/matita/matitaMathView.ml index f11354904..271a7b19a 100644 --- a/matita/matita/matitaMathView.ml +++ b/matita/matita/matitaMathView.ml @@ -27,680 +27,12 @@ open Printf -open GrafiteTypes open MatitaGtkMisc -open MatitaGuiTypes +open CicMathView module Stack = Continuationals.Stack -(** inherit from this class if you want to access current script *) -class scriptAccessor = -object (self) - method private script = MatitaScript.current () -end - let cicBrowsers = ref [] -let gui_instance = ref None -let set_gui gui = gui_instance := Some gui -let get_gui () = - match !gui_instance with - | None -> assert false - | Some gui -> gui - -let default_font_size () = - Helm_registry.get_opt_default Helm_registry.int - ~default:BuildTimeConf.default_font_size "matita.font_size" -let current_font_size = ref ~-1 -let increase_font_size () = incr current_font_size -let decrease_font_size () = decr current_font_size -let reset_font_size () = current_font_size := default_font_size () - - (* is there any lablgtk2 constant corresponding to the various mouse - * buttons??? *) -let left_button = 1 -let middle_button = 2 -let right_button = 3 - -let near (x1, y1) (x2, y2) = - let distance = sqrt (((x2 -. x1) ** 2.) +. ((y2 -. y1) ** 2.)) in - (distance < 4.) - -let mathml_ns = Gdome.domString "http://www.w3.org/1998/Math/MathML" -let xlink_ns = Gdome.domString "http://www.w3.org/1999/xlink" -let helm_ns = Gdome.domString "http://www.cs.unibo.it/helm" -let href_ds = Gdome.domString "href" -let maction_ds = Gdome.domString "maction" -let xref_ds = Gdome.domString "xref" - -let domImpl = Gdome.domImplementation () - - (** Gdome.element of a MathML document whose rendering should be blank. Used - * by cicBrowser to render "about:blank" document *) -let empty_mathml = lazy ( - domImpl#createDocument ~namespaceURI:(Some DomMisc.mathml_ns) - ~qualifiedName:(Gdome.domString "math") ~doctype:None) - -let empty_boxml = lazy ( - domImpl#createDocument ~namespaceURI:(Some DomMisc.boxml_ns) - ~qualifiedName:(Gdome.domString "box") ~doctype:None) - - (** shown for goals closed by side effects *) -let closed_goal_mathml = lazy "chiuso per side effect..." - -(* ids_to_terms should not be passed here, is just for debugging *) -let find_root_id annobj id ids_to_father_ids ids_to_terms ids_to_inner_types = - let find_parent id ids = - let rec aux id = -(* (prerr_endline (sprintf "id %s = %s" id - (try - CicPp.ppterm (Hashtbl.find ids_to_terms id) - with Not_found -> "NONE"))); *) - if List.mem id ids then Some id - else - (match - (try Hashtbl.find ids_to_father_ids id with Not_found -> None) - with - | None -> None - | Some id' -> aux id') - in - aux id - in - let return_father id ids = - match find_parent id ids with - | None -> assert false - | Some parent_id -> parent_id - in - let mk_ids terms = List.map CicUtil.id_of_annterm terms in - let inner_types = - Hashtbl.fold - (fun _ types acc -> - match types.Cic2acic.annexpected with - None -> types.Cic2acic.annsynthesized :: acc - | Some ty -> ty :: types.Cic2acic.annsynthesized :: acc - ) ids_to_inner_types [] in - match annobj with - | Cic.AConstant (_, _, _, Some bo, ty, _, _) - | Cic.AVariable (_, _, Some bo, ty, _, _) - | Cic.ACurrentProof (_, _, _, _, bo, ty, _, _) -> - return_father id (mk_ids (ty :: bo :: inner_types)) - | Cic.AConstant (_, _, _, None, ty, _, _) - | Cic.AVariable (_, _, None, ty, _, _) -> - return_father id (mk_ids (ty::inner_types)) - | Cic.AInductiveDefinition _ -> - assert false (* TODO *) - - (** @return string content of a dom node having a single text child node, e.g. - * bool *) -let string_of_dom_node node = - match node#get_firstChild with - | None -> "" - | Some node -> - (try - let text = new Gdome.text_of_node node in - text#get_data#to_string - with GdomeInit.DOMCastException _ -> "") - -let name_of_hypothesis = function - | Some (Cic.Name s, _) -> s - | _ -> assert false - -let id_of_node (node: Gdome.element) = - let xref_attr = - node#getAttributeNS ~namespaceURI:helm_ns ~localName:xref_ds in - try - List.hd (HExtlib.split ~sep:' ' xref_attr#to_string) - with Failure _ -> assert false - -type selected_term = - | SelTerm of Cic.term * string option (* term, parent hypothesis (if any) *) - | SelHyp of string * Cic.context (* hypothesis, context *) - -let hrefs_of_elt elt = - let localName = href_ds in - if elt#hasAttributeNS ~namespaceURI:xlink_ns ~localName then - let text = - (elt#getAttributeNS ~namespaceURI:xlink_ns ~localName)#to_string in - Some (HExtlib.split text) - else - None - -let rec has_maction (elt :Gdome.element) = - (* fix this comparison *) - if elt#get_tagName#to_string = "m:maction" || - elt#get_tagName#to_string = "b:action" then - true - else - match elt#get_parentNode with - | Some node when node#get_nodeType = GdomeNodeTypeT.ELEMENT_NODE -> - has_maction (new Gdome.element_of_node node) - | _ -> false -;; - -class clickableMathView obj = -let text_width = 80 in -object (self) - inherit GSourceView2.source_view obj - - method has_selection = (assert false : bool) - method strings_of_selection = (assert false : (paste_kind * string) list) - method update_font_size = - self#misc#modify_font_by_name - (sprintf "%s %d" BuildTimeConf.script_font !current_font_size) - method set_href_callback = (function _ -> () : (string -> unit) option -> unit) - method private set_cic_info = (function _ -> () : (Cic.conjecture option * (Cic.id, Cic.term) Hashtbl.t * - (Cic.id, Cic.hypothesis) Hashtbl.t * - (Cic.id, Cic.id option) Hashtbl.t * ('a, 'b) Hashtbl.t * 'c option) option -> unit) - (* dal widget di Luca *) - method load_root ~root = - self#buffer#delete ~start:(self#buffer#get_iter `START) - ~stop:(self#buffer#get_iter `END); - self#buffer#insert root - method remove_selections = (() : unit) - method set_selection = (fun _ -> () : Gdome.element option -> unit) - method get_selections = (assert false : Gdome.element list) - method set_font_size font_size = - self#misc#modify_font_by_name - (sprintf "%s %d" BuildTimeConf.script_font font_size) - - initializer - self#set_font_size !current_font_size; - self#source_buffer#set_language (Some MatitaGtkMisc.matita_lang); - self#source_buffer#set_highlight_syntax true; - self#set_editable false - -(* MATITA1.0 - inherit GMathViewAux.multi_selection_math_view obj - - val mutable href_callback: (string -> unit) option = None - method set_href_callback f = href_callback <- f - - val mutable _cic_info = None - method private set_cic_info info = _cic_info <- info - method private cic_info = _cic_info - - val normal_cursor = Gdk.Cursor.create `LEFT_PTR - val href_cursor = Gdk.Cursor.create `HAND2 - val maction_cursor = Gdk.Cursor.create `QUESTION_ARROW - - initializer - self#set_font_size !current_font_size; - ignore (self#connect#selection_changed self#choose_selection_cb); - ignore (self#event#connect#button_press self#button_press_cb); - ignore (self#event#connect#button_release self#button_release_cb); - ignore (self#event#connect#selection_clear self#selection_clear_cb); - ignore (self#connect#element_over self#element_over_cb); - ignore (self#coerce#misc#connect#selection_get self#selection_get_cb) - - val mutable button_press_x = -1. - val mutable button_press_y = -1. - val mutable selection_changed = false - val mutable href_statusbar_msg: - (GMisc.statusbar_context * Gtk.statusbar_message) option = None - (* *) - - method private selection_get_cb ctxt ~info ~time = - let text = - match ctxt#target with - | "PATTERN" -> self#text_of_selection `Pattern - | "TERM" | _ -> self#text_of_selection `Term - in - match text with - | None -> () - | Some s -> ctxt#return s - - method private text_of_selection fmt = - match self#get_selections with - | [] -> None - | node :: _ -> Some (self#string_of_node ~paste_kind:fmt node) - - method private selection_clear_cb sel_event = - self#remove_selections; - (GData.clipboard Gdk.Atom.clipboard)#clear (); - false - - method private button_press_cb gdk_button = - let button = GdkEvent.Button.button gdk_button in - if button = left_button then begin - button_press_x <- GdkEvent.Button.x gdk_button; - button_press_y <- GdkEvent.Button.y gdk_button; - selection_changed <- false - end else if button = right_button then - self#popup_contextual_menu - (self#get_element_at - (int_of_float (GdkEvent.Button.x gdk_button)) - (int_of_float (GdkEvent.Button.y gdk_button))) - (GdkEvent.Button.time gdk_button); - false - - method private element_over_cb (elt_opt, _, _, _) = - let win () = self#misc#window in - let leave_href () = - Gdk.Window.set_cursor (win ()) normal_cursor; - HExtlib.iter_option (fun (ctxt, msg) -> ctxt#remove msg) - href_statusbar_msg - in - match elt_opt with - | Some elt -> - if has_maction elt then - Gdk.Window.set_cursor (win ()) maction_cursor - else - (match hrefs_of_elt elt with - | Some ((_ :: _) as hrefs) -> - Gdk.Window.set_cursor (win ()) href_cursor; - let msg_text = (* now create statusbar msg and store it *) - match hrefs with - | [ href ] -> sprintf "Hyperlink to %s" href - | _ -> sprintf "Hyperlinks to: %s" (String.concat ", " hrefs) in - let ctxt = (get_gui ())#main#statusBar#new_context ~name:"href" in - let msg = ctxt#push msg_text in - href_statusbar_msg <- Some (ctxt, msg) - | _ -> leave_href ()) - | None -> leave_href () - - method private tactic_text_pattern_of_node node = - let id = id_of_node node in - let cic_info, unsh_sequent = self#get_cic_info id in - match self#get_term_by_id cic_info id with - | SelTerm (t, father_hyp) -> - let sequent = self#sequent_of_id ~paste_kind:`Pattern id in - let text = self#string_of_cic_sequent ~output_type:`Pattern sequent in - (match father_hyp with - | None -> None, [], Some text - | Some hyp_name -> None, [ hyp_name, text ], None) - | SelHyp (hyp_name, _ctxt) -> None, [ hyp_name, "%" ], None - - method private tactic_text_of_node node = - let id = id_of_node node in - let cic_info, unsh_sequent = self#get_cic_info id in - match self#get_term_by_id cic_info id with - | SelTerm (t, father_hyp) -> - let sequent = self#sequent_of_id ~paste_kind:`Term id in - let text = self#string_of_cic_sequent ~output_type:`Term sequent in - text - | SelHyp (hyp_name, _ctxt) -> hyp_name - - (** @return a pattern structure which contains pretty printed terms *) - method private tactic_text_pattern_of_selection = - match self#get_selections with - | [] -> assert false (* this method is invoked only if there's a sel. *) - | node :: _ -> self#tactic_text_pattern_of_node node - - method private popup_contextual_menu element time = - let menu = GMenu.menu () in - let add_menu_item ?(menu = menu) ?stock ?label () = - GMenu.image_menu_item ?stock ?label ~packing:menu#append () in - let check = add_menu_item ~label:"Check" () in - let reductions_menu_item = GMenu.menu_item ~label:"βδιζ-reduce" () in - let tactics_menu_item = GMenu.menu_item ~label:"Apply tactic" () in - let hyperlinks_menu_item = GMenu.menu_item ~label:"Hyperlinks" () in - menu#append reductions_menu_item; - menu#append tactics_menu_item; - menu#append hyperlinks_menu_item; - let reductions = GMenu.menu () in - let tactics = GMenu.menu () in - let hyperlinks = GMenu.menu () in - reductions_menu_item#set_submenu reductions; - tactics_menu_item#set_submenu tactics; - hyperlinks_menu_item#set_submenu hyperlinks; - let normalize = add_menu_item ~menu:reductions ~label:"Normalize" () in - let simplify = add_menu_item ~menu:reductions ~label:"Simplify" () in - let whd = add_menu_item ~menu:reductions ~label:"Weak head" () in - (match element with - | None -> hyperlinks_menu_item#misc#set_sensitive false - | Some elt -> - match hrefs_of_elt elt, href_callback with - | Some l, Some f -> - List.iter - (fun h -> - let item = add_menu_item ~menu:hyperlinks ~label:h () in - connect_menu_item item (fun () -> f h)) l - | _ -> hyperlinks_menu_item#misc#set_sensitive false); - menu#append (GMenu.separator_item ()); - let copy = add_menu_item ~stock:`COPY () in - let gui = get_gui () in - List.iter (fun item -> item#misc#set_sensitive gui#canCopy) - [ copy; check; normalize; simplify; whd ]; - let reduction_action kind () = - let pat = self#tactic_text_pattern_of_selection in - let statement = - let loc = HExtlib.dummy_floc in - "\n" ^ - GrafiteAstPp.pp_executable ~term_pp:(fun s -> s) - ~lazy_term_pp:(fun _ -> assert false) ~obj_pp:(fun _ -> assert false) - ~map_unicode_to_tex:(Helm_registry.get_bool - "matita.paste_unicode_as_tex") - (GrafiteAst.Tactic (loc, - Some (GrafiteAst.Reduce (loc, kind, pat)), - GrafiteAst.Semicolon loc)) in - (MatitaScript.current ())#advance ~statement () in - connect_menu_item copy gui#copy; - connect_menu_item normalize (reduction_action `Normalize); - connect_menu_item simplify (reduction_action `Simpl); - connect_menu_item whd (reduction_action `Whd); - menu#popup ~button:right_button ~time - - method private button_release_cb gdk_button = - if GdkEvent.Button.button gdk_button = left_button then begin - let button_release_x = GdkEvent.Button.x gdk_button in - let button_release_y = GdkEvent.Button.y gdk_button in - if selection_changed then - () - else (* selection _not_ changed *) - if near (button_press_x, button_press_y) - (button_release_x, button_release_y) - then - let x = int_of_float button_press_x in - let y = int_of_float button_press_y in - (match self#get_element_at x y with - | None -> () - | Some elt -> - if has_maction elt then ignore(self#action_toggle elt) else - (match hrefs_of_elt elt with - | Some hrefs -> self#invoke_href_callback hrefs gdk_button - | None -> ())) - end; - false - - method private invoke_href_callback hrefs gdk_button = - let button = GdkEvent.Button.button gdk_button in - if button = left_button then - let time = GdkEvent.Button.time gdk_button in - match href_callback with - | None -> () - | Some f -> - (match hrefs with - | [ uri ] -> f uri - | uris -> - let menu = GMenu.menu () in - List.iter - (fun uri -> - let menu_item = - GMenu.menu_item ~label:uri ~packing:menu#append () in - connect_menu_item menu_item - (fun () -> try f uri with Not_found -> assert false)) - uris; - menu#popup ~button ~time) - - method private choose_selection_cb gdome_elt = - let set_selection elt = - let misc = self#coerce#misc in - self#set_selection (Some elt); - misc#add_selection_target ~target:"STRING" Gdk.Atom.primary; - ignore (misc#grab_selection Gdk.Atom.primary); - in - let rec aux elt = - if (elt#getAttributeNS ~namespaceURI:helm_ns - ~localName:xref_ds)#to_string <> "" - then - set_selection elt - else - try - (match elt#get_parentNode with - | None -> assert false - | Some p -> aux (new Gdome.element_of_node p)) - with GdomeInit.DOMCastException _ -> () - in - (match gdome_elt with - | Some elt when (elt#getAttributeNS ~namespaceURI:xlink_ns - ~localName:href_ds)#to_string <> "" -> - set_selection elt - | Some elt -> aux elt - | None -> self#set_selection None); - selection_changed <- true - - method update_font_size = self#set_font_size !current_font_size - - (** find a term by id from stored CIC infos @return either `Hyp if the id - * correspond to an hypothesis or `Term (cic, hyp) if the id correspond to a - * term. In the latter case hyp is either None (if the term is a subterm of - * the sequent conclusion) or Some hyp_name if the term belongs to an - * hypothesis *) - method private get_term_by_id cic_info id = - let unsh_item, ids_to_terms, ids_to_hypotheses, ids_to_father_ids, _, _ = - cic_info in - let rec find_father_hyp id = - if Hashtbl.mem ids_to_hypotheses id - then Some (name_of_hypothesis (Hashtbl.find ids_to_hypotheses id)) - else - let father_id = - try Hashtbl.find ids_to_father_ids id - with Not_found -> assert false in - match father_id with - | Some id -> find_father_hyp id - | None -> None - in - try - let term = Hashtbl.find ids_to_terms id in - let father_hyp = find_father_hyp id in - SelTerm (term, father_hyp) - with Not_found -> - try - let hyp = Hashtbl.find ids_to_hypotheses id in - let _, context, _ = - match unsh_item with Some seq -> seq | None -> assert false in - let context' = MatitaMisc.list_tl_at hyp context in - SelHyp (name_of_hypothesis hyp, context') - with Not_found -> assert false - - method private find_obj_conclusion id = - match self#cic_info with - | None - | Some (_, _, _, _, _, None) -> assert false - | Some (_, ids_to_terms, _, ids_to_father_ids, ids_to_inner_types, Some annobj) -> - let id = - find_root_id annobj id ids_to_father_ids ids_to_terms ids_to_inner_types - in - (try Hashtbl.find ids_to_terms id with Not_found -> assert false) - - method private string_of_node ~(paste_kind:paste_kind) node = - if node#hasAttributeNS ~namespaceURI:helm_ns ~localName:xref_ds - then - match paste_kind with - | `Pattern -> - let tactic_text_pattern = self#tactic_text_pattern_of_node node in - GrafiteAstPp.pp_tactic_pattern - ~term_pp:(fun s -> s) ~lazy_term_pp:(fun _ -> assert false) - ~map_unicode_to_tex:(Helm_registry.get_bool - "matita.paste_unicode_as_tex") - tactic_text_pattern - | `Term -> self#tactic_text_of_node node - else string_of_dom_node node - - method private string_of_cic_sequent ~output_type cic_sequent = - let script = MatitaScript.current () in - let metasenv = - if script#onGoingProof () then script#proofMetasenv else [] in - let map_unicode_to_tex = - Helm_registry.get_bool "matita.paste_unicode_as_tex" in - ApplyTransformation.txt_of_cic_sequent_conclusion ~map_unicode_to_tex - ~output_type text_width metasenv cic_sequent - - method private pattern_of term father_hyp unsh_sequent = - let _, unsh_context, conclusion = unsh_sequent in - let where = - match father_hyp with - None -> conclusion - | Some name -> - let rec aux = - function - [] -> assert false - | Some (Cic.Name name', Cic.Decl ty)::_ when name' = name -> ty - | Some (Cic.Name name', Cic.Def (bo,_))::_ when name' = name-> bo - | _::tl -> aux tl - in - aux unsh_context - in - ProofEngineHelpers.pattern_of ~term:where [term] - - method private get_cic_info id = - match self#cic_info with - | Some ((Some unsh_sequent, _, _, _, _, _) as info) -> info, unsh_sequent - | Some ((None, _, _, _, _, _) as info) -> - let t = self#find_obj_conclusion id in - info, (~-1, [], t) (* dummy sequent for obj *) - | None -> assert false - - method private sequent_of_id ~(paste_kind:paste_kind) id = - let cic_info, unsh_sequent = self#get_cic_info id in - let cic_sequent = - match self#get_term_by_id cic_info id with - | SelTerm (t, father_hyp) -> -(* -IDIOTA: PRIMA SI FA LA LOCATE, POI LA PATTERN_OF. MEGLIO UN'UNICA pattern_of CHE PRENDA IN INPUT UN TERMINE E UN SEQUENTE. PER IL MOMENTO RISOLVO USANDO LA father_hyp PER RITROVARE L'IPOTESI PERDUTA -*) - let occurrences = - ProofEngineHelpers.locate_in_conjecture t unsh_sequent in - (match occurrences with - | [ context, _t ] -> - (match paste_kind with - | `Term -> ~-1, context, t - | `Pattern -> ~-1, [], self#pattern_of t father_hyp unsh_sequent) - | _ -> - HLog.error (sprintf "found %d occurrences while 1 was expected" - (List.length occurrences)); - assert false) (* since it uses physical equality *) - | SelHyp (_name, context) -> ~-1, context, Cic.Rel 1 in - cic_sequent - - method private string_of_selection ~(paste_kind:paste_kind) = - match self#get_selections with - | [] -> None - | node :: _ -> Some (self#string_of_node ~paste_kind node) - - method has_selection = self#get_selections <> [] - - (** @return an associative list format -> string with all possible selection - * formats. Rationale: in order to convert the selection to TERM or PATTERN - * format we need the sequent, the metasenv, ... keeping all of them in a - * closure would be more expensive than keeping their already converted - * forms *) - method strings_of_selection = - try - let misc = self#coerce#misc in - List.iter - (fun target -> misc#add_selection_target ~target Gdk.Atom.clipboard) - [ "TERM"; "PATTERN"; "STRING" ]; - ignore (misc#grab_selection Gdk.Atom.clipboard); - List.map - (fun paste_kind -> - paste_kind, HExtlib.unopt (self#string_of_selection ~paste_kind)) - [ `Term; `Pattern ] - with Failure _ -> failwith "no selection" -*) -end - -open GtkSourceView2 - -let clickableMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity = - SourceView.make_params [] ~cont:( - GtkText.View.make_params ~cont:( - GContainer.pack_container ~create:(fun pl -> - let obj = SourceView.new_ () in - Gobject.set_params (Gobject.try_cast obj "GtkSourceView") pl; - new clickableMathView obj))) - (* MATITA1.0 - GtkBase.Widget.size_params - ~cont:(OgtkSourceView2Props.pack_return (fun p -> - OgtkSourceView2Props.set_params - (new clickableMathView (GtkSourceView2Props.MathView_GMetaDOM.create p)) - ~font_size:None ~log_verbosity:None)) - [] - *) - -class cicMathView obj = -object (self) - inherit clickableMathView obj - - val mutable current_mathml = None - - method load_sequent metasenv metano = - let sequent = CicUtil.lookup_meta metano metasenv in - let (txt, unsh_sequent, - (_, (ids_to_terms, ids_to_father_ids, ids_to_hypotheses,_ ))) - = - ApplyTransformation.txt_of_cic_sequent_all - ~map_unicode_to_tex:false 80 (*MATITA 1.0??*) metasenv sequent - in - self#set_cic_info - (Some (Some unsh_sequent, - ids_to_terms, ids_to_hypotheses, ids_to_father_ids, - Hashtbl.create 1, None)); - (*MATITA 1.0 - if BuildTimeConf.debug then begin - let name = - "/tmp/sequent_viewer_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in - HLog.debug ("load_sequent: dumping MathML to ./" ^ name); - ignore (domImpl#saveDocumentToFile ~name ~doc:txt ()) - end; *) - self#load_root ~root:txt - - method nload_sequent: - 'status. #NCicCoercion.status as 'status -> NCic.metasenv -> - NCic.substitution -> int -> unit - = fun status metasenv subst metano -> - let sequent = List.assoc metano metasenv in - let txt = - ApplyTransformation.ntxt_of_cic_sequent - ~map_unicode_to_tex:false 80 status metasenv subst (metano,sequent) - in - (* MATITA 1.0 if BuildTimeConf.debug then begin - let name = - "/tmp/sequent_viewer_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in - HLog.debug ("load_sequent: dumping MathML to ./" ^ name); - ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ()) - end;*) - self#load_root ~root:txt - - method load_object obj = - let use_diff = false in (* ZACK TODO use XmlDiff when re-rendering? *) - let (txt, - (annobj, (ids_to_terms, ids_to_father_ids, _, ids_to_hypotheses, _, ids_to_inner_types))) - = - ApplyTransformation.txt_of_cic_object_all ~map_unicode_to_tex:false - 80 [] obj - in - self#set_cic_info - (Some (None, ids_to_terms, ids_to_hypotheses, ids_to_father_ids, ids_to_inner_types, Some annobj)); - (match current_mathml with - | Some current_mathml when use_diff -> -assert false (*MATITA1.0 - self#freeze; - XmlDiff.update_dom ~from:current_mathml mathml; - self#thaw*) - | _ -> - (* MATITA1.0 if BuildTimeConf.debug then begin - let name = - "/tmp/cic_browser_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in - HLog.debug ("cic_browser: dumping MathML to ./" ^ name); - ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ()) - end;*) - self#load_root ~root:txt; - current_mathml <- Some txt); - - method load_nobject : - 'status. #NCicCoercion.status as 'status -> NCic.obj -> unit - = fun status obj -> - let txt = ApplyTransformation.ntxt_of_cic_object ~map_unicode_to_tex:false - 80 status obj in -(* - self#set_cic_info - (Some (None, ids_to_terms, ids_to_hypotheses, ids_to_father_ids, ids_to_inner_types, Some annobj)); - (match current_mathml with - | Some current_mathml when use_diff -> - self#freeze; - XmlDiff.update_dom ~from:current_mathml mathml; - self#thaw - | _ -> -*) - (* MATITA1.0 if BuildTimeConf.debug then begin - let name = - "/tmp/cic_browser_" ^ string_of_int (Unix.getuid ()) ^ ".xml" in - HLog.debug ("cic_browser: dumping MathML to ./" ^ name); - ignore (domImpl#saveDocumentToFile ~name ~doc:mathml ()) - end;*) - self#load_root ~root:txt; - (*current_mathml <- Some mathml*)(*)*); -end let tab_label meta_markup = let rec aux = @@ -717,8 +49,6 @@ let goal_of_switch = function Stack.Open g | Stack.Closed g -> g class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = object (self) - inherit scriptAccessor - method cicMathView = cicMathView (** clickableMathView accessor *) val mutable pages = 0 @@ -726,7 +56,7 @@ class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = 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 = `Old [] + val mutable _metasenv = [],[] val mutable scrolledWin: GBin.scrolled_window option = None (* scrolled window to which the sequentViewer is currently attached *) val logo = (GMisc.image @@ -759,117 +89,31 @@ class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = GtkSignal.disconnect notebook#as_widget id; switch_page_callback <- None | None -> ()); - for i = 0 to pages do notebook#remove_page 0 done; + for _i = 0 to pages do notebook#remove_page 0 done; notebook#set_show_tabs true; pages <- 0; page2goal <- []; goal2page <- []; goal2win <- []; - _metasenv <- `Old []; - self#script#setGoal None - - method load_sequents : 'status. #NCicCoercion.status as 'status -> 'a - = fun status { proof= (_,metasenv,_subst,_,_, _) as proof; stack = stack } - -> - _metasenv <- `Old metasenv; - pages <- 0; - let win goal_switch = - let w = - GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`ALWAYS - ~shadow_type:`IN ~show:true () - in - let reparent () = - scrolledWin <- Some w; - match cicMathView#misc#parent with - | None -> w#add cicMathView#coerce - | Some parent -> - let parent = - match cicMathView#misc#parent with - None -> assert false - | Some p -> GContainer.cast_container p - in - parent#remove cicMathView#coerce; - w#add cicMathView#coerce - in - goal2win <- (goal_switch, reparent) :: goal2win; - w#coerce - in - assert ( - let stack_goals = Stack.open_goals stack in - let proof_goals = ProofEngineTypes.goals_of_proof proof in - if - HExtlib.list_uniq (List.sort Pervasives.compare stack_goals) - <> List.sort Pervasives.compare proof_goals - then begin - prerr_endline ("STACK GOALS = " ^ String.concat " " (List.map string_of_int stack_goals)); - prerr_endline ("PROOF GOALS = " ^ String.concat " " (List.map string_of_int proof_goals)); - false - end - else true - ); - let render_switch = - function Stack.Open i ->`Meta i | Stack.Closed i ->`Closed (`Meta i) - in - let page = ref 0 in - let added_goals = ref [] in - (* goals can be duplicated on the tack due to focus, but we should avoid - * multiple labels in the user interface *) - let add_tab markup goal_switch = - let goal = Stack.goal_of_switch goal_switch in - if not (List.mem goal !added_goals) then begin - ignore(notebook#append_page - ~tab_label:(tab_label markup) (win goal_switch)); - page2goal <- (!page, goal_switch) :: page2goal; - goal2page <- (goal_switch, !page) :: goal2page; - incr page; - pages <- pages + 1; - added_goals := goal :: !added_goals - end - in - let add_switch _ _ (_, sw) = add_tab (render_switch sw) sw in - Stack.iter (** populate notebook with tabs *) - ~env:(fun depth tag (pos, sw) -> - let markup = - match depth, pos with - | 0, 0 -> `Current (render_switch sw) - | 0, _ -> `Shift (pos, `Current (render_switch sw)) - | 1, pos when Stack.head_tag stack = `BranchTag -> - `Shift (pos, render_switch sw) - | _ -> render_switch sw - in - add_tab markup sw) - ~cont:add_switch ~todo:add_switch - stack; - switch_page_callback <- - Some (notebook#connect#switch_page ~callback:(fun page -> - let goal_switch = - try List.assoc page page2goal with Not_found -> assert false - in - self#script#setGoal (Some (goal_of_switch goal_switch)); - self#render_page status ~page ~goal_switch)) + _metasenv <- [],[] - method nload_sequents : 'status. #NTacStatus.tac_status as 'status -> unit - = fun status -> + method nload_sequents : 'status. #GrafiteTypes.status as 'status -> unit + = fun (status : #GrafiteTypes.status) -> let _,_,metasenv,subst,_ = status#obj in - _metasenv <- `New (metasenv,subst); + _metasenv <- metasenv,subst; pages <- 0; let win goal_switch = let w = GBin.scrolled_window ~hpolicy:`AUTOMATIC ~vpolicy:`ALWAYS - ~shadow_type:`IN ~show:true () - in + ~shadow_type:`IN ~show:true () in let reparent () = scrolledWin <- Some w; - match cicMathView#misc#parent with - | None -> w#add cicMathView#coerce - | Some parent -> - let parent = - match cicMathView#misc#parent with - None -> assert false - | Some p -> GContainer.cast_container p - in - parent#remove cicMathView#coerce; - w#add cicMathView#coerce + (match cicMathView#misc#parent with + | None -> () + | Some p -> + let parent = GContainer.cast_container p in + parent#remove cicMathView#coerce); + w#add cicMathView#coerce in goal2win <- (goal_switch, reparent) :: goal2win; w#coerce @@ -878,8 +122,8 @@ class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = let stack_goals = Stack.open_goals status#stack in let proof_goals = List.map fst metasenv in if - HExtlib.list_uniq (List.sort Pervasives.compare stack_goals) - <> List.sort Pervasives.compare proof_goals + HExtlib.list_uniq (List.sort compare stack_goals) + <> List.sort compare proof_goals then begin prerr_endline ("STACK GOALS = " ^ String.concat " " (List.map string_of_int stack_goals)); prerr_endline ("PROOF GOALS = " ^ String.concat " " (List.map string_of_int proof_goals)); @@ -908,7 +152,7 @@ class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = in let add_switch _ _ (_, sw) = add_tab (render_switch sw) sw in Stack.iter (** populate notebook with tabs *) - ~env:(fun depth tag (pos, sw) -> + ~env:(fun depth _tag (pos, sw) -> let markup = match depth, pos with | 0, 0 -> `Current (render_switch sw) @@ -925,28 +169,42 @@ class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = let goal_switch = try List.assoc page page2goal with Not_found -> assert false in - self#script#setGoal (Some (goal_of_switch goal_switch)); self#render_page status ~page ~goal_switch)) method private render_page: - 'status. #NCicCoercion.status as 'status -> page:int -> + 'status. #ApplyTransformation.status as 'status -> page:int -> goal_switch:Stack.switch -> unit - = fun status ~page ~goal_switch -> + = fun status ~page:_ ~goal_switch -> (match goal_switch with | Stack.Open goal -> - (match _metasenv with - `Old menv -> cicMathView#load_sequent menv goal - | `New (menv,subst) -> - cicMathView#nload_sequent status menv subst goal) - | Stack.Closed goal -> - let doc = Lazy.force closed_goal_mathml in - cicMathView#load_root ~root:doc); + let menv,subst = _metasenv in + cicMathView#nload_sequent status menv subst goal + | Stack.Closed _goal -> + let root = Lazy.force closed_goal_mathml in + cicMathView#load_root ~root); (try cicMathView#set_selection None; - List.assoc goal_switch goal2win () + List.assoc goal_switch goal2win (); + (match cicMathView#misc#parent with + None -> assert false + | Some p -> + (* The text widget dinamycally inserts the text in a separate + thread. We need to wait for it to terminate before we can + move the scrollbar to the end *) + while Glib.Main.pending()do ignore(Glib.Main.iteration false); done; + let w = + new GBin.scrolled_window + (Gobject.try_cast p#as_widget "GtkScrolledWindow") in + (* The double change upper/lower is to trigger the emission of + changed :-( *) + w#hadjustment#set_value w#hadjustment#upper; + w#hadjustment#set_value w#hadjustment#lower; + w#vadjustment#set_value w#vadjustment#lower; + w#vadjustment#set_value + (w#vadjustment#upper -. w#vadjustment#page_size)); with Not_found -> assert false) - method goto_sequent: 'status. #NCicCoercion.status as 'status -> int -> unit + method goto_sequent: 'status. #ApplyTransformation.status as 'status -> int -> unit = fun status goal -> let goal_switch, page = try @@ -957,60 +215,13 @@ class sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) () = in notebook#goto_page page; self#render_page status ~page ~goal_switch - end - (** constructors *) -type 'widget constructor = - ?hadjustment:GData.adjustment -> - ?vadjustment:GData.adjustment -> - ?font_size:int -> - ?log_verbosity:int -> - ?auto_indent:bool -> - ?highlight_current_line:bool -> - ?indent_on_tab:bool -> - ?indent_width:int -> - ?insert_spaces_instead_of_tabs:bool -> - ?right_margin_position:int -> - ?show_line_marks:bool -> - ?show_line_numbers:bool -> - ?show_right_margin:bool -> - ?smart_home_end:SourceView2Enums.source_smart_home_end_type -> - ?tab_width:int -> - ?editable:bool -> - ?cursor_visible:bool -> - ?justification:GtkEnums.justification -> - ?wrap_mode:GtkEnums.wrap_mode -> - ?accepts_tab:bool -> - ?border_width:int -> - ?width:int -> - ?height:int -> - ?packing:(GObj.widget -> unit) -> - ?show:bool -> unit -> - 'widget - -let cicMathView ?hadjustment ?vadjustment ?font_size ?log_verbosity = - SourceView.make_params [] ~cont:( - GtkText.View.make_params ~cont:( - GContainer.pack_container ~create:(fun pl -> - let obj = SourceView.new_ () in - Gobject.set_params (Gobject.try_cast obj "GtkSourceView") pl; - new cicMathView obj))) -(* MATITA 1.0 - GtkBase.Widget.size_params - ~cont:(OgtkMathViewProps.pack_return (fun p -> - OgtkMathViewProps.set_params - (new cicMathView (GtkMathViewProps.MathView_GMetaDOM.create p)) - ~font_size ~log_verbosity)) - [] -*) - let blank_uri = BuildTimeConf.blank_uri let current_proof_uri = BuildTimeConf.current_proof_uri type term_source = - [ `Ast of CicNotationPt.term - | `Cic of Cic.term * Cic.metasenv + [ `Ast of NotationPt.term | `NCic of NCic.term * NCic.context * NCic.metasenv * NCic.substitution | `String of string ] @@ -1025,11 +236,12 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) let dir_RE = Pcre.regexp "^cic:((/([^/]+/)*[^/]+(/)?)|/|)$" 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 = get_gui () in - let (win: MatitaGuiTypes.browserWin) = gui#newBrowserWin () in + let _gui = MatitaMisc.get_gui () in + let win = new MatitaGeneratedGui.browserWin () in + let _ = win#browserUri#misc#grab_focus () in let gviz = LablGraphviz.graphviz ~packing:win#graphScrolledWin#add () in let searchText = - GSourceView2.source_view ~auto_indent:false ~editable:false () + GSourceView3.source_view ~auto_indent:false ~editable:false () in let _ = win#scrolledwinContent#add (searchText :> GObj.widget); @@ -1078,7 +290,7 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) let module Pp = GraphvizPp.Dot in let filename, oc = Filename.open_temp_file "matita" ".dot" in let fmt = Format.formatter_of_out_channel oc in - let status = (MatitaScript.current ())#grafite_status in + let status = (get_matita_script_current ())#status in Pp.header ~name:"Hints" ~graph_type:"graph" @@ -1101,32 +313,27 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) ~name:"Coercions" ~node_attrs:["fontsize", "9"; "width", ".4"; "height", ".4"] ~edge_attrs:["fontsize", "10"] fmt; - let status = (MatitaScript.current ())#grafite_status in + let status = (get_matita_script_current ())#status in NCicCoercion.generate_dot_file status fmt; Pp.trailer fmt; - Pp.header - ~name:"OLDCoercions" - ~node_attrs:["fontsize", "9"; "width", ".4"; "height", ".4"] - ~edge_attrs:["fontsize", "10"] fmt; - CoercGraph.generate_dot_file fmt; - Pp.trailer fmt; Pp.raw "@." fmt; close_out oc; if tred then gviz#load_graph_from_file - ~gviz_cmd:"dot -Txdot | tred |gvpack -gv | dot" filename + (* gvpack can no longer read the output of -Txdot :-( *) + (*~gviz_cmd:"dot -Txdot | tred |gvpack -gv | dot" filename*) + ~gviz_cmd:"dot -Txdot | tred | dot" filename else gviz#load_graph_from_file - ~gviz_cmd:"dot -Txdot | gvpack -gv | dot" filename; + (* gvpack can no longer read the output of -Txdot :-( *) + (*~gviz_cmd:"dot -Txdot | gvpack -gv | dot" filename;*) + ~gviz_cmd:"dot -Txdot | dot" filename; HExtlib.safe_remove filename in object (self) - inherit scriptAccessor - - (* Whelp bar queries *) - - val mutable gviz_graph = MetadataDeps.DepGraph.dummy - val mutable gviz_uri = UriManager.uri_of_string "cic:/dummy.con"; + val mutable gviz_uri = + let uri = NUri.uri_of_string "cic:/dummy/dec.con" in + NReference.reference_of_spec uri NReference.Decl; val dep_contextual_menu = GMenu.menu () @@ -1152,60 +359,23 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) handle_error (fun () -> self#loadInput (self#_getSelectedUri ())))); mathView#set_href_callback (Some (fun uri -> handle_error (fun () -> - let uri = - try - `Uri (UriManager.uri_of_string uri) - with - UriManager.IllFormedUri _ -> - `NRef (NReference.reference_of_string uri) - in + let uri = `NRef (NReference.reference_of_string uri) in self#load uri))); gviz#connect_href (fun button_ev attrs -> let time = GdkEvent.Button.time button_ev in let uri = List.assoc "href" attrs in - gviz_uri <- UriManager.uri_of_string uri; + gviz_uri <- NReference.reference_of_string uri; match GdkEvent.Button.button button_ev with - | button when button = left_button -> self#load (`Uri gviz_uri) - | button when button = right_button -> + | button when button = MatitaMisc.left_button -> self#load (`NRef gviz_uri) + | button when button = MatitaMisc.right_button -> dep_contextual_menu#popup ~button ~time | _ -> ()); connect_menu_item win#browserCloseMenuItem (fun () -> let my_id = Oo.id self in cicBrowsers := List.filter (fun b -> Oo.id b <> my_id) !cicBrowsers; win#toplevel#misc#hide(); win#toplevel#destroy ()); - (* remove hbugs *) - (* - connect_menu_item win#hBugsTutorsMenuItem (fun () -> - self#load (`HBugs `Tutors)); - *) - win#hBugsTutorsMenuItem#misc#hide (); connect_menu_item win#browserUrlMenuItem (fun () -> win#browserUri#misc#grab_focus ()); - connect_menu_item win#univMenuItem (fun () -> - match self#currentCicUri with - | Some uri -> self#load (`Univs uri) - | None -> ()); - - (* fill dep graph contextual menu *) - let go_menu_item = - GMenu.image_menu_item ~label:"Browse it" - ~packing:dep_contextual_menu#append () in - let expand_menu_item = - GMenu.image_menu_item ~label:"Expand" - ~packing:dep_contextual_menu#append () in - let collapse_menu_item = - GMenu.image_menu_item ~label:"Collapse" - ~packing:dep_contextual_menu#append () in - dep_contextual_menu#append (go_menu_item :> GMenu.menu_item); - dep_contextual_menu#append (expand_menu_item :> GMenu.menu_item); - dep_contextual_menu#append (collapse_menu_item :> GMenu.menu_item); - connect_menu_item go_menu_item (fun () -> self#load (`Uri gviz_uri)); - connect_menu_item expand_menu_item (fun () -> - MetadataDeps.DepGraph.expand gviz_uri gviz_graph; - self#redraw_gviz ~center_on:gviz_uri ()); - connect_menu_item collapse_menu_item (fun () -> - MetadataDeps.DepGraph.collapse gviz_uri gviz_graph; - self#redraw_gviz ~center_on:gviz_uri ()); self#_load (`About `Blank); toplevel#show () @@ -1215,17 +385,15 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) (** @return None if no object uri can be built from the current entry *) method private currentCicUri = match current_entry with - | `Uri uri -> Some uri + | `NRef uri -> Some uri | _ -> None val model = new MatitaGtkMisc.taggedStringListModel tags win#whelpResultTreeview - val model_univs = - new MatitaGtkMisc.multiStringListModel ~cols:2 win#universesTreeview val mutable lastDir = "" (* last loaded "directory" *) - method mathView = (mathView :> MatitaGuiTypes.clickableMathView) + method mathView = mathView method private _getSelectedUri () = match model#easy_selection () with @@ -1261,12 +429,11 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) * * Use only these functions to switch between the tabs *) - method private _showMath = win#mathOrListNotebook#goto_page 0 - method private _showList = win#mathOrListNotebook#goto_page 1 - method private _showList2 = win#mathOrListNotebook#goto_page 5 - method private _showSearch = win#mathOrListNotebook#goto_page 6 - method private _showGviz = win#mathOrListNotebook#goto_page 3 - method private _showHBugs = win#mathOrListNotebook#goto_page 4 + method private _showMath = win#mathOrListNotebook#goto_page 0 + method private _showList = win#mathOrListNotebook#goto_page 1 + method private _showEgg = win#mathOrListNotebook#goto_page 2 + method private _showGviz = win#mathOrListNotebook#goto_page 3 + method private _showSearch = win#mathOrListNotebook#goto_page 4 method private back () = try @@ -1295,39 +462,35 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) | `About `TeX -> self#tex () | `About `Grammar -> self#grammar () | `Check term -> self#_loadCheck term - | `Cic (term, metasenv) -> self#_loadTermCic term metasenv | `NCic (term, ctx, metasenv, subst) -> self#_loadTermNCic term metasenv subst ctx | `Dir dir -> self#_loadDir dir - | `HBugs `Tutors -> self#_loadHBugsTutors - | `Uri uri -> self#_loadUriManagerUri uri - | `NRef nref -> self#_loadNReference nref - | `Univs uri -> self#_loadUnivs uri); + | `NRef nref -> self#_loadNReference nref); self#setEntry entry end) method private blank () = self#_showMath; - mathView#load_root "" + mathView#load_root (Lazy.force empty_mathml) - method private _loadCheck term = + method private _loadCheck _term = failwith "not implemented _loadCheck"; (* self#_showMath *) method private egg () = - win#mathOrListNotebook#goto_page 2; + self#_showEgg; Lazy.force load_easter_egg method private redraw_gviz ?center_on () = if Sys.command "which dot" = 0 then let tmpfile, oc = Filename.open_temp_file "matita" ".dot" in - let fmt = Format.formatter_of_out_channel oc in - MetadataDeps.DepGraph.render fmt gviz_graph; + (* MATITA 1.0 let fmt = Format.formatter_of_out_channel oc in + MetadataDeps.DepGraph.render fmt gviz_graph;*) close_out oc; gviz#load_graph_from_file ~gviz_cmd:"tred | dot" tmpfile; (match center_on with | None -> () - | Some uri -> gviz#center_on_href (UriManager.string_of_uri uri)); + | Some uri -> gviz#center_on_href (NReference.string_of_reference uri)); HExtlib.safe_remove tmpfile else MatitaGtkMisc.report_error ~title:"graphviz error" @@ -1335,7 +498,8 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) "the graph of dependencies amoung objects. Please install it.") ~parent:win#toplevel () - method private dependencies direction uri () = + method private dependencies _direction _uri () = + assert false (* MATITA 1.0 let dbd = LibraryDb.instance () in let graph = match direction with @@ -1343,7 +507,7 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) | `Back -> MetadataDeps.DepGraph.inverse_deps ~dbd uri in gviz_graph <- graph; (** XXX check this for memory consuption *) self#redraw_gviz ~center_on:uri (); - self#_showGviz + self#_showGviz *) method private coerchgraph tred () = load_coerchgraph tred (); @@ -1390,58 +554,26 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) self#_showSearch method private grammar () = - self#_loadText (Print_grammar.ebnf_of_term ()); + self#_loadText + (Print_grammar.ebnf_of_term (get_matita_script_current ())#status); method private home () = self#_showMath; - match self#script#grafite_status#proof_status with - | Proof (uri, metasenv, _subst, bo, ty, attrs) -> - let name = UriManager.name_of_uri (HExtlib.unopt uri) in - let obj = - Cic.CurrentProof (name, metasenv, Lazy.force bo, ty, [], attrs) - in - self#_loadObj obj - | Incomplete_proof { proof = (uri, metasenv, _subst, bo, ty, attrs) } -> - let name = UriManager.name_of_uri (HExtlib.unopt uri) in - let obj = - Cic.CurrentProof (name, metasenv, Lazy.force bo, ty, [], attrs) - in - self#_loadObj obj - | _ -> - match self#script#grafite_status#ng_mode with - `ProofMode -> - self#_loadNObj self#script#grafite_status - self#script#grafite_status#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 + let status = (get_matita_script_current ())#status in + match status#ng_mode with + `ProofMode -> self#_loadNObj status status#obj + | _ -> self#blank () method private _loadNReference (NReference.Ref (uri,_)) = - let obj = NCicEnvironment.get_checked_obj uri in - self#_loadNObj self#script#grafite_status obj - - method private _loadUnivs uri = - let uri = UriManager.strip_xpointer uri in - let (_, u) = CicEnvironment.get_obj CicUniv.empty_ugraph uri in - let _,us = CicUniv.do_rank u in - let l = - List.map - (fun u -> - [ CicUniv.string_of_universe u ; string_of_int (CicUniv.get_rank u)]) - us - in - self#_loadList2 l - + let status = (get_matita_script_current ())#status in + let obj = NCicEnvironment.get_checked_obj status uri in + self#_loadNObj status obj + method private _loadDir dir = let content = Http_getter.ls ~local:false dir in let l = List.fast_sort - Pervasives.compare + compare (List.map (function | Http_getter_types.Ls_section s -> "dir", s @@ -1451,20 +583,10 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) lastDir <- dir; self#_loadList l - method private _loadHBugsTutors = - self#_showHBugs - method private setEntry entry = win#browserUri#set_text (MatitaTypes.string_of_entry entry); current_entry <- entry - method private _loadObj obj = - (* showMath must be done _before_ loading the document, since if the - * widget is not mapped (hidden by the notebook) the document is not - * rendered *) - self#_showMath; - mathView#load_object obj - method private _loadNObj status obj = (* showMath must be done _before_ loading the document, since if the * widget is not mapped (hidden by the notebook) the document is not @@ -1472,17 +594,10 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) self#_showMath; mathView#load_nobject status obj - 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 _loadTermNCic term m s c = let d = 0 in let m = (0,([],c,term))::m in - let status = (MatitaScript.current ())#grafite_status in + let status = (get_matita_script_current ())#status in mathView#nload_sequent status m s d; self#_showMath @@ -1491,11 +606,6 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) List.iter (fun (tag, s) -> model#easy_append ~tag s) l; self#_showList - method private _loadList2 l = - model_univs#list_store#clear (); - List.iter model_univs#easy_mappend l; - self#_showList2 - (** { public methods, all must call _load!! } *) method load entry = @@ -1513,7 +623,7 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) let entry = match txt with | txt when is_uri txt -> - `Uri (UriManager.uri_of_string ((*fix_uri*) txt)) + `NRef (NReference.reference_of_string ((*fix_uri*) txt)) | txt when is_dir txt -> `Dir (MatitaMisc.normalize_dir txt) | txt -> (try @@ -1525,10 +635,6 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) self#_load entry; self#_historyAdd entry - (** {2 methods accessing underlying GtkMathView} *) - - method updateFontSize = mathView#set_font_size !current_font_size - (** {2 methods used by constructor only} *) method win = win @@ -1541,9 +647,9 @@ class cicBrowser_impl ~(history:MatitaTypes.mathViewer_entry MatitaMisc.history) let sequentsViewer ~(notebook:GPack.notebook) ~(cicMathView:cicMathView) (): MatitaGuiTypes.sequentsViewer = - new sequentsViewer ~notebook ~cicMathView () + (new sequentsViewer ~notebook ~cicMathView ():> MatitaGuiTypes.sequentsViewer) -let cicBrowser () = +let new_cicBrowser () = let size = BuildTimeConf.browser_history_size in let rec aux history = let browser = new cicBrowser_impl ~history () in @@ -1561,108 +667,53 @@ let cicBrowser () = GdkKeysyms._W (fun () -> win#toplevel#destroy ()); *) cicBrowsers := browser :: !cicBrowsers; - (browser :> MatitaGuiTypes.cicBrowser) + browser in let history = new MatitaMisc.browser_history size (`About `Blank) in aux history -let default_cicMathView () = cicMathView ~show:true () -let cicMathView_instance = MatitaMisc.singleton default_cicMathView +(** @param reuse if set reused last opened cic browser otherwise +* opens a new one. default is false *) +let cicBrowser ?(reuse=false) t = + let browser = + if reuse then + (match !cicBrowsers with [] -> new_cicBrowser () | b :: _ -> b) + else + new_cicBrowser () + in + match t with + None -> () + | Some t -> browser#load t +;; + +let default_cicMathView () = + let res = cicMathView ~show:true () in + res#set_href_callback + (Some (fun uri -> + let uri = `NRef (NReference.reference_of_string uri) in + cicBrowser (Some uri))); + res -let default_sequentsViewer () = - let gui = get_gui () in +let cicMathView_instance = + MatitaMisc.singleton default_cicMathView + +let default_sequentsViewer notebook = let cicMathView = cicMathView_instance () in - sequentsViewer ~notebook:gui#main#sequentsNotebook ~cicMathView () -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 :> MatitaGuiTypes.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 - - method screenshot status sequents metasenv subst (filename as ofn) = - () (*MATITA 1.0 - let w = GWindow.window ~title:"screenshot" () in - let width = 500 in - let height = 2000 in - let m = GMathView.math_view - ~font_size:!current_font_size ~width ~height - ~packing:w#add - ~show:true () - in - w#show (); - let filenames = - HExtlib.list_mapi - (fun (mno,_ as sequent) i -> - let mathml = - ApplyTransformation.nmml_of_cic_sequent - status metasenv subst sequent - in - m#load_root ~root:mathml#get_documentElement; - let pixmap = m#get_buffer in - let pixbuf = GdkPixbuf.create ~width ~height () in - GdkPixbuf.get_from_drawable ~dest:pixbuf pixmap; - let filename = - filename ^ "-raw" ^ string_of_int i ^ ".png" - in - GdkPixbuf.save ~filename ~typ:"png" pixbuf; - filename,mno) - sequents - in - let items = - List.map (fun (x,mno) -> - ignore(Sys.command - (Printf.sprintf - ("convert "^^ - " '(' -gravity west -bordercolor grey -border 1 label:%d ')' "^^ - " '(' -trim -bordercolor white -border 5 "^^ - " -bordercolor grey -border 1 %s ')' -append %s ") - mno - (Filename.quote x) - (Filename.quote (x ^ ".label.png")))); - x ^ ".label.png") - filenames - in - let rec div2 = function - | [] -> [] - | [x] -> [[x]] - | x::y::tl -> [x;y] :: div2 tl - in - let items = div2 items in - ignore(Sys.command (Printf.sprintf - "convert %s -append %s" - (String.concat "" - (List.map (fun items -> - Printf.sprintf " '(' %s +append ')' " - (String.concat - (" '(' -gravity center -size 10x10 xc: ')' ") items)) items)) - (Filename.quote (ofn ^ ".png")))); - List.iter (fun x,_ -> Sys.remove x) filenames; - List.iter Sys.remove (List.flatten items); - w#destroy (); - *) - end + sequentsViewer ~notebook ~cicMathView () + +let sequentsViewer_instance = + let already_used = ref false in + fun notebook -> + if !already_used then assert false + else + (already_used := true; + default_sequentsViewer notebook) let refresh_all_browsers () = List.iter (fun b -> b#refresh ~force:false ()) !cicBrowsers -let update_font_sizes () = - List.iter (fun b -> b#updateFontSize) !cicBrowsers; - (cicMathView_instance ())#update_font_size - let get_math_views () = - ((cicMathView_instance ()) :> MatitaGuiTypes.clickableMathView) - :: (List.map (fun b -> b#mathView) !cicBrowsers) + (cicMathView_instance ()) :: (List.map (fun b -> b#mathView) !cicBrowsers) let find_selection_owner () = let rec aux = @@ -1671,7 +722,7 @@ let find_selection_owner () = | mv :: tl -> (match mv#get_selections with | [] -> aux tl - | sel :: _ -> mv) + | _sel :: _ -> mv) in aux (get_math_views ())