capitalize variants

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5044 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2002-07-25 22:51:47 +00:00
parent f12a554a0d
commit 27da263ceb
8 changed files with 33 additions and 33 deletions

View File

@ -409,7 +409,7 @@ class editor ~top ~menus = object (self)
end else begin
match Jg_message.ask ~master:top ~title:"Save"
("File `" ^ name ^ "' exists. Overwrite it?")
with `yes -> () | `no | `cancel -> raise Exit
with `Yes -> Sys.remove name | `No | `Cancel -> raise Exit
end;
let file = open_out name in
let text = Text.get txt.tw ~start:tstart ~stop:(tposend 1) in
@ -432,9 +432,9 @@ class editor ~top ~menus = object (self)
if Textvariable.get txt.modified = "modified" then
begin match Jg_message.ask ~master:top ~title:"Open"
("`" ^ Filename.basename txt.name ^ "' modified. Save it?")
with `yes -> self#save_text txt
| `no -> ()
| `cancel -> raise Exit
with `Yes -> self#save_text txt
| `No -> ()
| `Cancel -> raise Exit
end;
Checkbutton.deselect label;
(Text.index current_tw ~index:(`Mark"insert", []), [])
@ -469,9 +469,9 @@ class editor ~top ~menus = object (self)
if Textvariable.get txt.modified = "modified" then
begin match Jg_message.ask ~master:top ~title:"Close"
("`" ^ Filename.basename txt.name ^ "' modified. Save it?")
with `yes -> self#save_text txt
| `no -> ()
| `cancel -> raise Exit
with `Yes -> self#save_text txt
| `No -> ()
| `Cancel -> raise Exit
end;
windows <- exclude txt windows;
if windows = [] then
@ -495,9 +495,9 @@ class editor ~top ~menus = object (self)
if Textvariable.get txt.modified = "modified" then
match Jg_message.ask ~master:top ~title:"Quit" ~cancel
("`" ^ Filename.basename txt.name ^ "' modified. Save it?")
with `yes -> self#save_text txt
| `no -> ()
| `cancel -> raise Exit
with `Yes -> self#save_text txt
| `No -> ()
| `Cancel -> raise Exit
end;
bind top ~events:[`Destroy];
destroy top

View File

@ -87,13 +87,13 @@ let ask ~title ?master ?(no=true) ?(cancel=true) text =
~width:250 ~justify:`Left ~aspect:400 ~anchor:`W
and fw = Frame.create tl
and sync = Textvariable.create ~on:tl ()
and r = ref (`cancel : [`yes|`no|`cancel]) in
and r = ref (`Cancel : [`Yes|`No|`Cancel]) in
let accept = Button.create fw ~text:(if no then "Yes" else "Dismiss")
~command:(fun () -> r := `yes; destroy tl)
~command:(fun () -> r := `Yes; destroy tl)
and refuse = Button.create fw ~text:"No"
~command:(fun () -> r := `no; destroy tl)
~command:(fun () -> r := `No; destroy tl)
and cancelB = Button.create fw ~text:"Cancel"
~command:(fun () -> r := `cancel; destroy tl)
~command:(fun () -> r := `Cancel; destroy tl)
in
bind tl ~events:[`Destroy] ~extend:true
~action:(fun _ -> Textvariable.set sync "1");

View File

@ -27,4 +27,4 @@ val formatted :
val ask :
title:string -> ?master:toplevel widget ->
?no:bool -> ?cancel:bool -> string -> [`cancel|`no|`yes]
?no:bool -> ?cancel:bool -> string -> [`Cancel|`No|`Yes]

View File

@ -213,8 +213,8 @@ let get_fields ~prefix ~sign self =
let rec search_type_in_signature t ~sign ~prefix ~mode =
let matches = match mode with
`included -> included t ~prefix
| `exact -> equal t ~prefix
`Included -> included t ~prefix
| `Exact -> equal t ~prefix
and lid_of_id id = mklid (prefix @ [Ident.name id]) in
List2.flat_map sign ~f:
begin fun item -> match item with
@ -260,9 +260,9 @@ let rec search_type_in_signature t ~sign ~prefix ~mode =
let search_all_types t ~mode =
let tl = match mode, t.desc with
`exact, _ -> [t]
| `included, Tarrow _ -> [t]
| `included, _ ->
`Exact, _ -> [t]
| `Included, Tarrow _ -> [t]
| `Included, _ ->
[t; newty(Tarrow("",t,newvar(),Cok)); newty(Tarrow("",newvar(),t,Cok))]
in List2.flat_map !module_list ~f:
begin fun modname ->

View File

@ -33,7 +33,7 @@ val string_of_kind : pkind -> string
exception Error of int * int
val search_string_type :
string -> mode:[`exact|`included] -> (Longident.t * pkind) list
string -> mode:[`Exact|`Included] -> (Longident.t * pkind) list
val search_pattern_symbol : string -> (Longident.t * pkind) list
val search_string_symbol : string -> (Longident.t * pkind) list

View File

@ -121,7 +121,7 @@ object (self)
len
with Unix.Unix_error _ -> 0
end;
method history (dir : [`next|`previous]) =
method history (dir : [`Next|`Previous]) =
if not h#empty then begin
if reading then begin
Text.delete textw ~start:(`Mark"input",[`Char 1])
@ -131,7 +131,7 @@ object (self)
Text.mark_set textw ~mark:"input"
~index:(`Mark"insert",[`Char(-1)])
end;
self#insert (if dir = `previous then h#previous else h#next)
self#insert (if dir = `Previous then h#previous else h#next)
end
method private lex ?(start = `Mark"insert",[`Linestart])
?(stop = `Mark"insert",[`Lineend]) () =
@ -176,10 +176,10 @@ object (self)
([], `KeyRelease, [`Char], fun ev -> self#keyrelease ev.ev_Char);
(* [], `KeyPressDetail"Return", [], fun _ -> self#return; *)
([], `ButtonPressDetail 2, [`MouseX; `MouseY], self#paste);
([`Alt], `KeyPressDetail"p", [], fun _ -> self#history `previous);
([`Alt], `KeyPressDetail"n", [], fun _ -> self#history `next);
([`Meta], `KeyPressDetail"p", [], fun _ -> self#history `previous);
([`Meta], `KeyPressDetail"n", [], fun _ -> self#history `next);
([`Alt], `KeyPressDetail"p", [], fun _ -> self#history `Previous);
([`Alt], `KeyPressDetail"n", [], fun _ -> self#history `Next);
([`Meta], `KeyPressDetail"p", [], fun _ -> self#history `Previous);
([`Meta], `KeyPressDetail"n", [], fun _ -> self#history `Next);
([`Control], `KeyPressDetail"c", [], fun _ -> self#interrupt);
([], `Destroy, [], fun _ -> self#kill) ]
in
@ -356,9 +356,9 @@ let f ~prog ~title =
end;
file_menu#add_command "Close" ~command:(fun () -> destroy tl);
history_menu#add_command "Previous " ~accelerator:"M-p"
~command:(fun () -> (!sh)#history `previous);
~command:(fun () -> (!sh)#history `Previous);
history_menu#add_command "Next" ~accelerator:"M-n"
~command:(fun () -> (!sh)#history `next);
~command:(fun () -> (!sh)#history `Next);
signal_menu#add_command "Interrupt " ~accelerator:"C-c"
~command:(fun () -> (!sh)#interrupt);
signal_menu#add_command "Kill" ~command:(fun () -> (!sh)#kill)

View File

@ -36,7 +36,7 @@ class shell :
method interrupt : unit
method insert : string -> unit
method send : string -> unit
method history : [`next|`previous] -> unit
method history : [`Next|`Previous] -> unit
end
val kill_all : unit -> unit

View File

@ -169,10 +169,10 @@ let search_string ?(mode="symbol") ew =
begin match guess_search_mode text with
`Long -> search_string_symbol text
| `Pattern -> search_pattern_symbol text
| `Type -> search_string_type text ~mode:`included
| `Type -> search_string_type text ~mode:`Included
end
| "Type" -> search_string_type text ~mode:`included
| "Exact" -> search_string_type text ~mode:`exact
| "Type" -> search_string_type text ~mode:`Included
| "Exact" -> search_string_type text ~mode:`Exact
| _ -> assert false
in
match l with [] -> ()