diff options
author | Jacques Garrigue <garrigue at math.nagoya-u.ac.jp> | 2001-09-27 07:31:55 +0000 |
---|---|---|
committer | Jacques Garrigue <garrigue at math.nagoya-u.ac.jp> | 2001-09-27 07:31:55 +0000 |
commit | 4e056bc4d41ba7a1bb75a860eaa3be1c26ccd0ff (patch) | |
tree | ad1e3b4b6ce34b93a7364dd5adb98528c8fda159 | |
parent | dadb2acc94b375a210fa778c88d69cc77e5eb003 (diff) |
ameliore ocamlbrowser
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3800 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | otherlibs/labltk/browser/README | 87 | ||||
-rw-r--r-- | otherlibs/labltk/browser/help.ml | 102 | ||||
-rw-r--r-- | otherlibs/labltk/browser/main.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/browser/searchpos.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/browser/viewer.ml | 122 |
5 files changed, 185 insertions, 132 deletions
diff --git a/otherlibs/labltk/browser/README b/otherlibs/labltk/browser/README index 21fdbd0c2..e48ba6f9c 100644 --- a/otherlibs/labltk/browser/README +++ b/otherlibs/labltk/browser/README @@ -9,75 +9,90 @@ INSTALLATION The name of the command is `ocamlbrowser'. USE - OCamlBrowser is composed of three tools, the Editor, which allows - one to edit/typecheck/analyse .mli and .ml files, the Viewer, to - walk around compiled modules, and the Shell, to run an OCaml - subshell. You may only have one instance of Editor and Viewer, but - you may use several subshells. + OCamlBrowser is composed of three tools, the Viewer, to walk around + compiled modules, the Editor, which allows one to + edit/typecheck/analyse .mli and .ml files, and the Shell, to run an + OCaml subshell. You may only have one instance of Editor and + Viewer, but you may use several subshells. As with the compiler, you may specify a different path for the - standard library by setting OCAMLDIR. You may also extend the + standard library by setting CAMLLIB. You may also extend the initial load path (only standard library by default) by using the - -I command line option. + -I command line option, or set various other options (see -help). -a) Viewer - It displays the list of modules in the load path. Click on one to - start your trip. + If you prefered the old GUI, it is still available with the option + -oldui, otherwise you get a new Smalltalkish user interface. - The entry line at the bottom allows one to search for an identifier - in all modules, either by its name (? and * patterns allowed) or by - its type (if there is an arrow in the input). When search by type - is used, it is done in inclusion mode (cf. Modules - search symbol) +1) Viewer - The Close all button is there to dismiss the windows created - during your trip (every click creates one...) By double-clicking on - it you will quit the browser. + Menus File - Open and File - Editor give access to the editor. File - Shell opens an OCaml shell. + View - Show all defs displays all the interface of the currently + selected module + View - Search entry shows/hides the search entry at the top of the + window + Modules - Path editor changes the load path. Pressing [Add to path] or Insert key adds selected directories to the load path. Pressing [Remove from path] or Delete key removes selected paths from the load path. Modules - Reset cache rescans the load path and resets the module - cache. Do it if you recompile some interface, or change the load - path in a conflictual way. + cache. Do it if you recompile some interface, or change the load + path in a conflictual way. Modules - Search symbol allows to search a symbol either by its - name, like the bottom line of the viewer, or, more interestingly, - by its type. Exact type searches for a type with exactly the same - information as the pattern (variables match only variables), - included type allows to give only partial information: the actual - type may take more arguments and return more results, and variables - in the pattern match anything. In both cases, argument and tuple - order is irrelevant (*), and unlabeled arguments in the pattern - match any label. + name, like the bottom line of the viewer, or, more + interestingly, by its type. Exact type searches for a type + with exactly the same information as the pattern (variables + match only variables), included type allows to give only + partial information: the actual type may take more arguments + and return more results, and variables in the pattern match + anything. In both cases, argument and tuple order is + irrelevant (*), and unlabeled arguments in the pattern match + any label. (*) To avoid combinatorial explosion of the search space, optional arguments in the actual type are ignored if (1) there are to many of them, and (2) they do not appear explicitly in the pattern. -b) Module walking - Each module is displayed in its own window. + Search entry + + The entry line at the top allows one to search for an identifier + in all modules, either by its name (? and * patterns allowed) or by + its type. When search by type is used, it is done in inclusion mode + (cf. Modules - search symbol) + + The Close all button at the bottom is there to dismiss the windows + created by the Detach button. By double-clicking on it you will + quit the browser. + + Module browsing + + You select a module in the leftmost box by either cliking on it or + pressing return when it is selected. Fast access is available in + all boxes pressing the first few letter of the desired + name. Double-clicking / double-return displays the whole signature + for the module. - At the top, a scrollable list of the defined identifiers. If you - click on one, this will either create a new window (if this is a - sub-module) or display the signature for this identifier below. + Defined identifiers inside the module are displayed in a box to the + right of the previous one. If you click on one, this will either + display its contents in another box (if this is a sub-module) or + display the signature for this identifier below. Signatures are clickable. Double clicking with the left mouse - button on an identifier in a signature brings you to its signature, - inside its module box. + button on an identifier in a signature brings you to its signature. A single click on the right button pops up a menu displaying the type declaration for the selected identifier. Its title, when selectable, also brings you to its signature. At the bottom, a series of buttons, depending on the context. - * Show all displays the signature of the whole module. * Detach copies the currently displayed signature in a new window, - to keep it. + to keep it. You can discard these windows with Close all. * Impl and Intf bring you to the implementation or interface of the currently displayed signature, if it is available. diff --git a/otherlibs/labltk/browser/help.ml b/otherlibs/labltk/browser/help.ml index 696e1d85b..d21fd1261 100644 --- a/otherlibs/labltk/browser/help.ml +++ b/otherlibs/labltk/browser/help.ml @@ -1,81 +1,92 @@ let text = " OCamlBrowser Help USE - OCamlBrowser is composed of three tools, the Editor, which allows - one to edit/typecheck/analyse .mli and .ml files, the Viewer, to - walk around compiled modules, and the Shell, to run an OCaml - subshell. You may only have one instance of Editor and Viewer, but - you may use several subshells. + OCamlBrowser is composed of three tools, the Viewer, to walk around + compiled modules, the Editor, which allows one to + edit/typecheck/analyse .mli and .ml files, and the Shell, to run an + OCaml subshell. You may only have one instance of Editor and + Viewer, but you may use several subshells. As with the compiler, you may specify a different path for the - standard library by setting OCAMLDIR. You may also extend the + standard library by setting CAMLLIB. You may also extend the initial load path (only standard library by default) by using the - -I command line option. + -I command line option, or set various other options (see -help). -1) Viewer - It displays the list of modules in the load path. Click on one to - start your trip. + If you prefered the old GUI, it is still available with the option + -oldui, otherwise you get a new Smalltalkish user interface. - The entry line at the bottom allows one to search for an identifier - in all modules, either by its name (? and * patterns allowed) or by - its type (if there is an arrow in the input). When search by type - is used, it is done in inclusion mode (cf. Modules - search symbol) +1) Viewer - The Close all button is there to dismiss the windows created - during your trip (every click creates one...) By double-clicking on - it you will quit the browser. + Menus File - Open and File - Editor give access to the editor. File - Shell opens an OCaml shell. + View - Show all defs displays all the interface of the currently + selected module + View - Search entry shows/hides the search entry at the top of the + window + Modules - Path editor changes the load path. Pressing [Add to path] or Insert key adds selected directories to the load path. Pressing [Remove from path] or Delete key removes selected paths from the load path. Modules - Reset cache rescans the load path and resets the module - cache. Do it if you recompile some interface, or change the load - path in a conflictual way. + cache. Do it if you recompile some interface, or change the load + path in a conflictual way. Modules - Search symbol allows to search a symbol either by its - name, like the bottom line of the viewer, or, more interestingly, - by its type. Exact type searches for a type with exactly the same - information as the pattern (variables match only variables), - included type allows to give only partial information: the actual - type may take more arguments and return more results, and variables - in the pattern match anything. In both cases, argument and tuple - order is irrelevant (*), and unlabeled arguments in the pattern - match any label. - - (*) To avoid combinatorial explosion of the search space, optional - arguments in the actual type are ignored if (1) there are to many - of them, and (2) they do not appear explicitly in the pattern. - -2) Module walking - Each module is displayed in its own window. - - At the top, a scrollable list of the defined identifiers. If you - click on one, this will either create a new window (if this is a - sub-module) or display the signature for this identifier below. + name, like the bottom line of the viewer, or, more + interestingly, by its type. Exact type searches for a type + with exactly the same information as the pattern (variables + match only variables), included type allows to give only + partial information: the actual type may take more arguments + and return more results, and variables in the pattern match + anything. In both cases, argument and tuple order is + irrelevant, and unlabeled arguments in the pattern match + any label. + + Search entry + + The entry line at the top allows one to search for an identifier + in all modules, either by its name (? and * patterns allowed) or by + its type. When search by type is used, it is done in inclusion mode + (cf. Modules - search symbol) + + The Close all button at the bottom is there to dismiss the windows + created by the Detach button. By double-clicking on it you will + quit the browser. + + Module browsing + + You select a module in the leftmost box by either cliking on it or + pressing return when it is selected. Fast access is available in + all boxes pressing the first few letter of the desired + name. Double-clicking / double-return displays the whole signature + for the module. + + Defined identifiers inside the module are displayed in a box to the + right of the previous one. If you click on one, this will either + display its contents in another box (if this is a sub-module) or + display the signature for this identifier below. Signatures are clickable. Double clicking with the left mouse - button on an identifier in a signature brings you to its signature, - inside its module box. + button on an identifier in a signature brings you to its signature. A single click on the right button pops up a menu displaying the type declaration for the selected identifier. Its title, when selectable, also brings you to its signature. At the bottom, a series of buttons, depending on the context. - * Show all displays the signature of the whole module. * Detach copies the currently displayed signature in a new window, - to keep it. + to keep it. You can discard these windows with Close all. * Impl and Intf bring you to the implementation or interface of the currently displayed signature, if it is available. C-s opens a text search dialog for the displayed signature. -3) File editor +2) Editor You can edit files with it, but there is no auto-save nor undo at the moment. Otherwise you can use it as a browser, making occasional corrections. @@ -104,7 +115,7 @@ USE Signature shows the signature of the current file. -4) Shell +3) Shell When you create a shell, a dialog is presented to you, letting you choose which command you want to run, and the title of the shell (to choose it in the Editor). @@ -120,6 +131,9 @@ USE BUGS +* This not really a bug, but OCamlBrowser is a huge memory consumer. + Go and buy some. + * When you quit the editor and some file was modified, a dialogue is displayed asking wether you want to really quit or not. But 1) if you quit directly from the viewer, there is no dialogue at all, and diff --git a/otherlibs/labltk/browser/main.ml b/otherlibs/labltk/browser/main.ml index d82812244..a1fa4b876 100644 --- a/otherlibs/labltk/browser/main.ml +++ b/otherlibs/labltk/browser/main.ml @@ -44,7 +44,7 @@ let _ = \032 U/u enable/disable unused match case\n\ \032 V/v enable/disable hidden instance variable\n\ \032 X/x enable/disable all other warnings\n\ - \032 default setting is A (all warnings enabled)" ] + \032 default setting is \"Al\" (all warnings but labels enabled)" ] (fun name -> raise(Arg.Bad("don't know what to do with " ^ name))) "ocamlbrowser :"; Config.load_path := diff --git a/otherlibs/labltk/browser/searchpos.ml b/otherlibs/labltk/browser/searchpos.ml index 674864eae..b0495ace1 100644 --- a/otherlibs/labltk/browser/searchpos.ml +++ b/otherlibs/labltk/browser/searchpos.ml @@ -323,7 +323,7 @@ let rec view_signature ?title ?path ?(env = !start_env) ?(detach=false) sign = Pack.forget [mw.mw_edit; mw.mw_intf]; List.iter ~f:destroy (Winfo.children mw.mw_frame); Label.configure label ~text:title; - pack [label] ~fill:`X; + pack [label] ~fill:`X ~side:`Bottom; Jg_message.formatted ~title ~on:mw.mw_frame ~maxheight:15 () | None, _ -> raise Not_found | Some path, _ -> @@ -336,7 +336,7 @@ let rec view_signature ?title ?path ?(env = !start_env) ?(detach=false) sign = begin match mw.mw_title with None -> () | Some label -> Label.configure label ~text:title; - pack [label] ~fill:`X + pack [label] ~fill:`X ~side:`Bottom end; Button.configure mw.mw_detach ~command:(fun () -> view_signature sign ~title ~env ~detach:true); diff --git a/otherlibs/labltk/browser/viewer.ml b/otherlibs/labltk/browser/viewer.ml index 0240dfe3b..10142851f 100644 --- a/otherlibs/labltk/browser/viewer.ml +++ b/otherlibs/labltk/browser/viewer.ml @@ -158,7 +158,29 @@ let guess_search_mode s : [`Type | `Long | `Pattern] = done; if !is_type then `Type else if !is_long then `Long else `Pattern -let search_which = ref "itself" + +let search_string ?(mode="symbol") ew = + let text = Entry.get ew in + try + if text = "" then () else + let l = match mode with + "Name" -> + begin match guess_search_mode text with + `Long -> search_string_symbol text + | `Pattern -> search_pattern_symbol text + | `Type -> search_string_type text ~mode:`included + end + | "Type" -> search_string_type text ~mode:`included + | "Exact" -> search_string_type text ~mode:`exact + | _ -> assert false + in + match l with [] -> () + | [lid,kind] -> view_symbol lid ~kind ~env:!start_env + | l -> choose_symbol ~title:"Choose symbol" ~env:!start_env l + with Searchid.Error (s,e) -> + Entry.icursor ew ~index:(`Num s) + +let search_which = ref "Name" let search_symbol () = if !module_list = [] then @@ -169,35 +191,16 @@ let search_symbol () = let choice = Frame.create tl and which = Textvariable.create ~on:tl () in let itself = Radiobutton.create choice ~text:"Itself" - ~variable:which ~value:"itself" + ~variable:which ~value:"Name" and extype = Radiobutton.create choice ~text:"Exact type" - ~variable:which ~value:"exact" + ~variable:which ~value:"Exact" and iotype = Radiobutton.create choice ~text:"Included type" - ~variable:which ~value:"iotype" + ~variable:which ~value:"Type" and buttons = Frame.create tl in let search = Button.create buttons ~text:"Search" ~command: begin fun () -> search_which := Textvariable.get which; - let text = Entry.get ew in - try if text = "" then () else - let l = - match !search_which with - "itself" -> - begin match guess_search_mode text with - `Long -> search_string_symbol text - | `Pattern -> search_pattern_symbol text - | `Type -> search_string_type text ~mode:`included - end - | "iotype" -> search_string_type text ~mode:`included - | "exact" -> search_string_type text ~mode:`exact - | _ -> assert false - in - if l <> [] then - choose_symbol ~title:"Choose symbol" ~env:!start_env l - with Searchid.Error (s,e) -> - Entry.selection_clear ew; - Entry.selection_range ew ~start:(`Num s) ~stop:(`Num e); - Entry.xview_index ew ~index:(`Num s) + search_string ew ~mode:!search_which end and ok = Jg_button.create_destroyer tl ~parent:buttons ~text:"Cancel" in @@ -301,6 +304,8 @@ let show_help () = let fw, tw, sb = Jg_text.create_with_scrollbar tl in let ok = Jg_button.create_destroyer ~parent:tl ~text:"Ok" tl in Text.insert tw ~index:tend ~text:Help.text; + Text.configure tw ~state:`Disabled; + Jg_bind.enter_focus tw; pack [tw] ~side:`Left ~fill:`Both ~expand:true; pack [sb] ~side:`Right ~fill:`Y; pack [fw] ~side:`Top ~expand:true ~fill:`Both; @@ -334,24 +339,8 @@ let f ?(dir=Unix.getcwd()) ?on () = let ew = Entry.create tl in let buttons = Frame.create tl in - let search = Button.create buttons ~text:"Search" ~pady:1 ~command: - begin fun () -> - let s = Entry.get ew in - let mode = guess_search_mode s in - let l = - match mode with - | `Long -> search_string_symbol s - | `Pattern -> search_pattern_symbol s - | `Type -> - try search_string_type ~mode:`included s - with Searchid.Error (start,stop) -> - Entry.icursor ew ~index:(`Num start); [] - in - match l with [] -> () - | [lid,kind] when mode = `Long -> - view_symbol lid ~kind ~env:!start_env - | _ -> choose_symbol ~title:"Choose symbol" ~env:!start_env l - end + let search = Button.create buttons ~text:"Search" ~pady:1 + ~command:(fun () -> search_string ew) and close = Button.create buttons ~text:"Close all" ~pady:1 ~command:close_all_views in @@ -404,8 +393,9 @@ class st_viewer ?(dir=Unix.getcwd()) ?on () = and modmenu = new Jg_menu.c "Modules" ~parent:menus and viewmenu = new Jg_menu.c "View" ~parent:menus and helpmenu = new Jg_menu.c "Help" ~parent:menus in + let search_frame = Frame.create tl in let boxes_frame = Frame.create tl ~name:"boxes" in - let label = Label.create tl ~anchor:`W ~padx:10 in + let label = Label.create tl ~anchor:`W ~padx:5 in let view = Frame.create tl in let buttons = Frame.create tl in let all = Button.create buttons ~text:"Show all" ~padx:20 @@ -426,6 +416,25 @@ object (self) fmbox, mbox initializer + (* Search *) + let ew = Entry.create search_frame + and searchtype = Textvariable.create ~on:tl () in + bind ew ~events:[`KeyPressDetail "Return"] ~action: + (fun _ -> search_string ew ~mode:(Textvariable.get searchtype)); + Jg_bind.enter_focus ew; + let search_button ?value text = + Radiobutton.create search_frame + ~text ~variable:searchtype ~value:text in + let symbol = search_button "Name" + and atype = search_button "Type" in + Radiobutton.select symbol; + pack [Label.create search_frame ~text:"Search"] ~side:`Left ~ipadx:5; + pack [ew] ~fill:`X ~expand:true ~side:`Left; + pack [Label.create search_frame ~text:"by"] ~side:`Left ~ipadx:5; + pack [symbol; atype] ~side:`Left; + pack [Label.create search_frame] ~side:`Right + + initializer (* Boxes *) let fmbox, mbox = self#create_box in Jg_box.add_completion mbox ~nocase:true ~double:false ~action: @@ -434,6 +443,8 @@ object (self) end; bind mbox ~events:[`Modified([`Double], `ButtonPressDetail 1)] ~action:(fun _ -> show_all ()); + bind mbox ~events:[`Modified([`Double], `KeyPressDetail "Return")] + ~action:(fun _ -> show_all ()); Setpath.add_update_hook (fun () -> reset_modules mbox; self#hide_after 1); List.iter [1;2] ~f:(fun _ -> ignore self#create_box); Searchpos.default_frame := Some @@ -452,6 +463,22 @@ object (self) filemenu#add_command "Shell..." ~command:start_shell; filemenu#add_command "Quit" ~command:(fun () -> destroy tl); + (* View menu *) + viewmenu#add_command "Show all defs" ~command:(fun () -> show_all ()); + let show_search = Textvariable.create ~on:tl () in + Textvariable.set show_search "1"; + Menu.add_checkbutton viewmenu#menu ~label:"Search Entry" + ~variable:show_search ~indicatoron:true ~state:`Active + ~command: + begin fun () -> + let v = Textvariable.get show_search in + if v = "1" then begin + Pack.forget [boxes_frame]; + pack [search_frame] ~fill:`X ~expand:true; + pack [boxes_frame] ~fill:`Both ~expand:true + end else Pack.forget [search_frame] + end; + (* modules menu *) modmenu#add_command "Path editor..." ~command:(fun () -> Setpath.set ~dir); @@ -459,17 +486,14 @@ object (self) ~command:(fun () -> reset_modules mbox; Env.reset_cache ()); modmenu#add_command "Search symbol..." ~command:search_symbol; - (* View menu *) - viewmenu#add_command "Show all" ~command:(fun () -> show_all ()); - (* Help menu *) helpmenu#add_command "Manual..." ~command:show_help; - pack [filemenu#button; modmenu#button; viewmenu#button] + pack [filemenu#button; viewmenu#button; modmenu#button] ~side:`Left ~ipadx:5 ~anchor:`W; pack [helpmenu#button] ~side:`Right ~anchor:`E ~ipadx:5; - pack [menus] ~side:`Top ~fill:`X; - (* pack [close; search] ~fill:`X ~side:`Right ~expand:true; *) + pack [menus] ~fill:`X; + pack [search_frame] ~fill:`X ~expand:true; pack [boxes_frame] ~fill:`Both ~expand:true; pack [buttons] ~fill:`X ~side:`Bottom ~expand:false; pack [view] ~fill:`Both ~side:`Bottom ~expand:true; |