]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/gTopLevel/gTopLevel.ml
basic MathQL support
[helm.git] / helm / gTopLevel / gTopLevel.ml
index 800e69aa07b485cd326638ad3b3f5ba33caee01c..49510a9dde1dc7f9a2480df7d7a7afc11caf686f 100644 (file)
@@ -53,6 +53,7 @@ let htmlheader_and_content = ref htmlheader;;
 
 let current_cic_infos = ref None;;
 let current_goal_infos = ref None;;
+let current_scratch_infos = ref None;;
 
 
 (* MISC FUNCTIONS *)
@@ -82,12 +83,6 @@ let c2 = parseStyle "annotatedpres.xsl";;
 
 let getterURL = Configuration.getter_url;;
 let processorURL = Configuration.processor_url;;
-(*
-let processorURL = "http://phd.cs.unibo.it:8080/helm/servelt/uwobo/";;
-let getterURL = "http://phd.cs.unibo.it:8081/";;
-let processorURL = "http://localhost:8080/helm/servelt/uwobo/";;
-let getterURL = "http://localhost:8081/";;
-*)
 
 let mml_styles = [d_c ; c1 ; g ; c2 ; l];;
 let mml_args =
@@ -156,7 +151,7 @@ let mml_of_cic_object uri annobj ids_to_inner_sorts ids_to_inner_types =
 (*CSC: We save the innertypes to disk so that we can retrieve them in the  *)
 (*CSC: stylesheet. This DOES NOT work when UWOBO and/or the getter are not *)
 (*CSC: local.                                                              *)
-   Xml.pp xmlinnertypes (Some "/public/sacerdot/innertypes") ;
+   Xml.pp xmlinnertypes (Some "/public/fguidi/innertypes") ;
    let output = applyStylesheets input mml_styles mml_args in
     output
 ;;
@@ -164,50 +159,60 @@ let mml_of_cic_object uri annobj ids_to_inner_sorts ids_to_inner_types =
 
 (* CALLBACKS *)
 
+exception RefreshSequentException of exn;;
+exception RefreshProofException of exn;;
+
 let refresh_proof (output : GMathView.math_view) =
- let uri,currentproof =
-  match !ProofEngine.proof with
-     None -> assert false
-   | Some (uri,metasenv,bo,ty) ->
-      uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty))
- in
- let
-  (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,ids_to_inner_types)
- =
-  Cic2acic.acic_object_of_cic_object currentproof
- in
-  let mml = mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types in
-   output#load_tree mml ;
-   current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
+ try
+  let uri,currentproof =
+   match !ProofEngine.proof with
+      None -> assert false
+    | Some (uri,metasenv,bo,ty) ->
+       uri,(Cic.CurrentProof (UriManager.name_of_uri uri, metasenv, bo, ty))
+  in
+   let
+    (acic,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,ids_to_inner_types)
+   =
+    Cic2acic.acic_object_of_cic_object currentproof
+   in
+    let mml =
+     mml_of_cic_object uri acic ids_to_inner_sorts ids_to_inner_types
+    in
+     output#load_tree mml ;
+     current_cic_infos := Some (ids_to_terms,ids_to_father_ids)
+ with
+  e -> raise (RefreshProofException e)
 ;;
 
 let refresh_sequent (proofw : GMathView.math_view) =
- match !ProofEngine.goal with
-    None -> proofw#unload
-  | Some (_,currentsequent) ->
-     let metasenv =
-      match !ProofEngine.proof with
-         None -> assert false
-       | Some (_,metasenv,_,_) -> metasenv
-     in
-      let sequent_gdome,ids_to_terms,ids_to_father_ids =
-       SequentPp.XmlPp.print_sequent metasenv currentsequent
+ try
+  match !ProofEngine.goal with
+     None -> proofw#unload
+   | Some (_,currentsequent) ->
+      let metasenv =
+       match !ProofEngine.proof with
+          None -> assert false
+        | Some (_,metasenv,_,_) -> metasenv
       in
-       let sequent_doc =
-        Xml2Gdome.document_of_xml domImpl sequent_gdome
+       let sequent_gdome,ids_to_terms,ids_to_father_ids =
+        SequentPp.XmlPp.print_sequent metasenv currentsequent
        in
-        let sequent_mml =
-         applyStylesheets sequent_doc sequent_styles sequent_args
+        let sequent_doc =
+         Xml2Gdome.document_of_xml domImpl sequent_gdome
         in
-         proofw#load_tree ~dom:sequent_mml ;
-         current_goal_infos := Some (ids_to_terms,ids_to_father_ids)
+         let sequent_mml =
+          applyStylesheets sequent_doc sequent_styles sequent_args
+         in
+          proofw#load_tree ~dom:sequent_mml ;
+          current_goal_infos := Some (ids_to_terms,ids_to_father_ids)
+ with
+  e -> raise (RefreshSequentException e)
+;;
+
 (*
 ignore(domImpl#saveDocumentToFile ~doc:sequent_doc
  ~name:"/public/sacerdot/guruguru1" ~indent:true ()) ;
-ignore(domImpl#saveDocumentToFile ~doc:sequent_mml
- ~name:"/public/sacerdot/guruguru2" ~indent:true ())
 *)
-;;
 
 let mml_of_cic_term term =
  let context =
@@ -226,9 +231,11 @@ let mml_of_cic_term term =
     let sequent_doc =
      Xml2Gdome.document_of_xml domImpl sequent_gdome
     in
-     applyStylesheets sequent_doc sequent_styles sequent_args
-     (*CSC: magari prima o poi serve*)
-     (*current_scratch_infos := Some (ids_to_terms,ids_to_father_ids)*)
+     let res =
+      applyStylesheets sequent_doc sequent_styles sequent_args ;
+     in
+      current_scratch_infos := Some (term,ids_to_terms,ids_to_father_ids) ;
+      res
 ;;
 
 let output_html outputhtml msg =
@@ -253,11 +260,26 @@ let call_tactic tactic rendering_window () =
     refresh_sequent proofw ;
     refresh_proof output
    with
-    e ->
-     output_html outputhtml
-      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
-     ProofEngine.proof := savedproof ;
-     ProofEngine.goal := savedgoal ;
+      RefreshSequentException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+       refresh_sequent proofw
+    | RefreshProofException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
+       refresh_sequent proofw ;
+       refresh_proof output
+    | e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+       ProofEngine.proof := savedproof ;
+       ProofEngine.goal := savedgoal ;
   end
 ;;
 
@@ -279,7 +301,9 @@ let call_tactic_with_input tactic rendering_window () =
    in
    let context =
     List.map
-     (function (_,n,_) -> n)
+     (function
+         ProofEngine.Definition (n,_)
+       | ProofEngine.Declaration (n,_) -> n)
      (match !ProofEngine.goal with
          None -> assert false
        | Some (_,(ctx,_)) -> ctx
@@ -299,11 +323,26 @@ let call_tactic_with_input tactic rendering_window () =
     with
        CicTextualParser0.Eof ->
         inputt#delete_text 0 inputlen
+     | RefreshSequentException e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+          "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+        ProofEngine.proof := savedproof ;
+        ProofEngine.goal := savedgoal ;
+        refresh_sequent proofw
+     | RefreshProofException e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+          "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+        ProofEngine.proof := savedproof ;
+        ProofEngine.goal := savedgoal ;
+        refresh_sequent proofw ;
+        refresh_proof output
      | e ->
         output_html outputhtml
-         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>");
+         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
         ProofEngine.proof := savedproof ;
-        ProofEngine.goal := savedgoal
+        ProofEngine.goal := savedgoal ;
 ;;
 
 let call_tactic_with_goal_input tactic rendering_window () =
@@ -333,9 +372,26 @@ let call_tactic_with_goal_input tactic rendering_window () =
                refresh_proof rendering_window#output
            | None -> assert false (* "ERROR: No current term!!!" *)
          with
-          e ->
-           output_html outputhtml
-            ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+            RefreshSequentException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent proofw
+          | RefreshProofException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent proofw ;
+             refresh_proof output
+          | e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
         end
    | None ->
       output_html outputhtml
@@ -376,7 +432,9 @@ let call_tactic_with_input_and_goal_input tactic rendering_window () =
                 in
                 let context =
                  List.map
-                  (function (_,n,_) -> n)
+                  (function
+                      ProofEngine.Definition (n,_)
+                    | ProofEngine.Declaration (n,_) -> n)
                   (match !ProofEngine.goal with
                       None -> assert false
                     | Some (_,(ctx,_)) -> ctx
@@ -401,6 +459,60 @@ let call_tactic_with_input_and_goal_input tactic rendering_window () =
                       inputt#delete_text 0 inputlen
                  end
            | None -> assert false (* "ERROR: No current term!!!" *)
+         with
+            RefreshSequentException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "sequent: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent proofw
+          | RefreshProofException e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+               "proof: " ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+             refresh_sequent proofw ;
+             refresh_proof output
+          | e ->
+             output_html outputhtml
+              ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+             ProofEngine.proof := savedproof ;
+             ProofEngine.goal := savedgoal ;
+        end
+   | None ->
+      output_html outputhtml
+       ("<h1 color=\"red\">No term selected</h1>")
+;;
+
+let call_tactic_with_goal_input_in_scratch tactic scratch_window () =
+ let module L = LogicalOperations in
+ let module G = Gdome in
+  let mmlwidget = (scratch_window#mmlwidget : GMathView.math_view) in
+  let outputhtml = (scratch_window#outputhtml : GHtml.xmhtml) in
+  let savedproof = !ProofEngine.proof in
+  let savedgoal  = !ProofEngine.goal in
+   match mmlwidget#get_selection with
+     Some node ->
+      let xpath =
+       ((node : Gdome.element)#getAttributeNS
+         ~namespaceURI:helmns
+         ~localName:(G.domString "xref"))#to_string
+      in
+       if xpath = "" then assert false (* "ERROR: No xref found!!!" *)
+       else
+        begin
+         try
+          match !current_scratch_infos with
+             (* term is the whole goal in the scratch_area *)
+             Some (term,ids_to_terms, ids_to_father_ids) ->
+              let id = xpath in
+               let expr = tactic term (Hashtbl.find ids_to_terms id) in
+                let mml = mml_of_cic_term expr in
+                 scratch_window#show () ;
+                 scratch_window#mmlwidget#load_tree ~dom:mml
+           | None -> assert false (* "ERROR: No current term!!!" *)
          with
           e ->
            output_html outputhtml
@@ -439,7 +551,23 @@ let cut rendering_window =
 let change rendering_window =
  call_tactic_with_input_and_goal_input ProofEngine.change rendering_window
 ;;
+let letin rendering_window =
+ call_tactic_with_input ProofEngine.letin rendering_window
+;;
+
 
+let whd_in_scratch scratch_window =
+ call_tactic_with_goal_input_in_scratch ProofEngine.whd_in_scratch
+  scratch_window
+;;
+let reduce_in_scratch scratch_window =
+ call_tactic_with_goal_input_in_scratch ProofEngine.reduce_in_scratch
+  scratch_window
+;;
+let simpl_in_scratch scratch_window =
+ call_tactic_with_goal_input_in_scratch ProofEngine.simpl_in_scratch
+  scratch_window
+;;
 
 
 
@@ -501,9 +629,17 @@ let proveit rendering_window () =
               refresh_sequent rendering_window#proofw
           | None -> assert false (* "ERROR: No current term!!!" *)
         with
-         e ->
-          output_html outputhtml
-           ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+           RefreshSequentException e ->
+            output_html outputhtml
+             ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+              "sequent: " ^ Printexc.to_string e ^ "</h1>")
+         | RefreshProofException e ->
+            output_html outputhtml
+             ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+              "proof: " ^ Printexc.to_string e ^ "</h1>")
+         | e ->
+            output_html outputhtml
+             ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
        end
   | None -> assert false (* "ERROR: No selection!!!" *)
 ;;
@@ -532,14 +668,22 @@ let open_ rendering_window () =
       ProofEngine.proof :=
        Some (uri, metasenv, bo, ty) ;
       ProofEngine.goal := None ;
-      inputt#delete_text 0 inputlen ;
-      ignore(oldinputt#insert_text input oldinputt#length) ;
       refresh_sequent proofw ;
       refresh_proof output ;
+      inputt#delete_text 0 inputlen ;
+      ignore(oldinputt#insert_text input oldinputt#length)
    with
-    e ->
-     output_html outputhtml
-      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
+      RefreshSequentException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "sequent: " ^ Printexc.to_string e ^ "</h1>")
+    | RefreshProofException e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+         "proof: " ^ Printexc.to_string e ^ "</h1>")
+    | e ->
+       output_html outputhtml
+        ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
 let state rendering_window () =
@@ -558,23 +702,26 @@ let state rendering_window () =
       match CicTextualParser.main CicTextualLexer.token lexbuf with
          None -> ()
        | Some expr ->
-          try
-           let _  = CicTypeChecker.type_of_aux' [] [] expr in
-            ProofEngine.proof :=
-             Some (UriManager.uri_of_string "cic:/dummy.con",
-                    [1,expr], Cic.Meta 1, expr) ;
-            ProofEngine.goal := Some (1,([],expr)) ;
-            refresh_sequent proofw ;
-            refresh_proof output ;
-          with
-           e ->
-            print_endline ("? " ^ CicPp.ppterm expr) ;
-            raise e
+          let _  = CicTypeChecker.type_of_aux' [] [] expr in
+           ProofEngine.proof :=
+            Some (UriManager.uri_of_string "cic:/dummy.con",
+                   [1,expr], Cic.Meta 1, expr) ;
+           ProofEngine.goal := Some (1,([],expr)) ;
+           refresh_sequent proofw ;
+           refresh_proof output ;
      done
     with
        CicTextualParser0.Eof ->
         inputt#delete_text 0 inputlen ;
         ignore(oldinputt#insert_text input oldinputt#length)
+     | RefreshSequentException e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+          "sequent: " ^ Printexc.to_string e ^ "</h1>")
+     | RefreshProofException e ->
+        output_html outputhtml
+         ("<h1 color=\"red\">Exception raised during the refresh of the " ^
+          "proof: " ^ Printexc.to_string e ^ "</h1>")
      | e ->
         output_html outputhtml
          ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
@@ -598,8 +745,12 @@ let check rendering_window scratch_window () =
        None -> []
      | Some (_,(ctx,_)) -> ctx
    in
-    ProofEngine.cic_context_of_context context,
-     List.map (function (_,n,_) -> n) context
+    ProofEngine.cic_context_of_named_context context,
+     List.map
+      (function
+          ProofEngine.Declaration (n,_)
+        | ProofEngine.Definition (n,_) -> n
+      ) context
   in
    (* Do something interesting *)
    let lexbuf = Lexing.from_string input in
@@ -614,22 +765,44 @@ let check rendering_window scratch_window () =
        | Some expr ->
           try
            let ty  = CicTypeChecker.type_of_aux' metasenv ciccontext expr in
-            let mml = mml_of_cic_term ty in
+            let mml = mml_of_cic_term (Cic.Cast (expr,ty)) in
              scratch_window#show () ;
-             scratch_window#display ~dom:mml
+             scratch_window#mmlwidget#load_tree ~dom:mml
           with
            e ->
             print_endline ("? " ^ CicPp.ppterm expr) ;
             raise e
      done
     with
-       CicTextualParser0.Eof ->
-        inputt#delete_text 0 inputlen
+       CicTextualParser0.Eof -> ()
      | e ->
        output_html outputhtml
         ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>") ;
 ;;
 
+let locate rendering_window () =
+ let inputt = (rendering_window#inputt : GEdit.text) in
+ let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
+  let inputlen = inputt#length in
+  let input = inputt#get_chars 0 inputlen in
+   try   
+    output_html outputhtml (Mquery.locate input) ;
+    inputt#delete_text 0 inputlen 
+   with
+    e -> 
+     output_html outputhtml
+      ("<h1 color=\"red\">" ^ Printexc.to_string e ^ "</h1>")
+;;
+
+let backward rendering_window () =
+   let outputhtml = (rendering_window#outputhtml : GHtml.xmhtml) in
+   let result =
+      match !ProofEngine.goal with
+         | None -> ""
+         | Some (_, (_, t)) -> (Mquery.backward t)
+      in 
+   output_html outputhtml result
+      
 let choose_selection
      (mmlwidget : GMathView.math_view) (element : Gdome.element option)
 =
@@ -777,16 +950,38 @@ end;;
 
 (* Scratch window *)
 
-class scratch_window () =
+class scratch_window outputhtml =
  let window =
   GWindow.window ~title:"MathML viewer" ~border_width:2 () in
+ let vbox =
+  GPack.vbox ~packing:window#add () in
+ let hbox =
+  GPack.hbox ~packing:(vbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let whdb =
+  GButton.button ~label:"Whd"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let reduceb =
+  GButton.button ~label:"Reduce"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let simplb =
+  GButton.button ~label:"Simpl"
+   ~packing:(hbox#pack ~expand:false ~fill:false ~padding:5) () in
+ let scrolled_window =
+  GBin.scrolled_window ~border_width:10
+   ~packing:(vbox#pack ~expand:true ~padding:5) () in
  let mmlwidget =
-  GMathView.math_view ~packing:(window#add) ~width:400 ~height:280 () in
+  GMathView.math_view
+   ~packing:(scrolled_window#add) ~width:400 ~height:280 () in
 object(self)
- method display = mmlwidget#load_tree
- method show = window#show
+ method outputhtml = outputhtml
+ method mmlwidget = mmlwidget
+ method show () = window#misc#hide () ; window#show ()
  initializer
-  ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true ))
+  ignore(mmlwidget#connect#selection_changed (choose_selection mmlwidget)) ;
+  ignore(window#event#connect#delete (fun _ -> window#misc#hide () ; true )) ;
+  ignore(whdb#connect#clicked (whd_in_scratch self)) ;
+  ignore(reduceb#connect#clicked (reduce_in_scratch self)) ;
+  ignore(simplb#connect#clicked (simpl_in_scratch self))
 end;;
 
 (* Main window *)
@@ -835,6 +1030,12 @@ class rendering_window output proofw (label : GMisc.label) =
  let checkb =
   GButton.button ~label:"Check"
    ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+ let locateb =
+  GButton.button ~label:"Locate"
+   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
+ let backwardb =
+  GButton.button ~label:"Backward"
+   ~packing:(hbox4#pack ~expand:false ~fill:false ~padding:5) () in
  let inputt = GEdit.text ~editable:true ~width:400 ~height: 100
    ~packing:(vbox#pack ~padding:5) () in
  let vbox1 =
@@ -875,20 +1076,23 @@ class rendering_window output proofw (label : GMisc.label) =
  let changeb =
   GButton.button ~label:"Change"
    ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
+ let letinb =
+  GButton.button ~label:"Let ... In"
+   ~packing:(hbox3#pack ~expand:false ~fill:false ~padding:5) () in
  let outputhtml =
   GHtml.xmhtml
    ~source:"<html><body bgColor=\"white\"></body></html>"
    ~width:400 ~height: 200
    ~packing:(vbox1#pack ~expand:false ~fill:false ~padding:5)
    ~show:true () in
- let scratch_window = new scratch_window () in
+ let scratch_window = new scratch_window outputhtml in
 object(self)
  method outputhtml = outputhtml
  method oldinputt = oldinputt
  method inputt = inputt
  method output = (output : GMathView.math_view)
  method proofw = (proofw : GMathView.math_view)
- method show () = window#show ()
+ method show = window#show
  initializer
   button_export_to_postscript#misc#set_sensitive false ;
 
@@ -907,6 +1111,8 @@ object(self)
   ignore(stateb#connect#clicked (state self)) ;
   ignore(openb#connect#clicked (open_ self)) ;
   ignore(checkb#connect#clicked (check self scratch_window)) ;
+  ignore(locateb#connect#clicked (locate self)) ;
+  ignore(backwardb#connect#clicked (backward self)) ;
   ignore(exactb#connect#clicked (exact self)) ;
   ignore(applyb#connect#clicked (apply self)) ;
   ignore(elimintrosb#connect#clicked (elimintros self)) ;
@@ -916,6 +1122,7 @@ object(self)
   ignore(foldb#connect#clicked (fold self)) ;
   ignore(cutb#connect#clicked (cut self)) ;
   ignore(changeb#connect#clicked (change self)) ;
+  ignore(letinb#connect#clicked (letin self)) ;
   ignore(introsb#connect#clicked (intros self)) ;
   Logger.log_callback :=
    (Logger.log_to_html ~print_and_flush:(output_html outputhtml))