diff options
Diffstat (limited to 'otherlibs/labltk/browser')
-rw-r--r-- | otherlibs/labltk/browser/editor.ml | 10 | ||||
-rw-r--r-- | otherlibs/labltk/browser/fileselect.ml | 16 | ||||
-rw-r--r-- | otherlibs/labltk/browser/jg_completion.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/browser/searchid.ml | 60 | ||||
-rw-r--r-- | otherlibs/labltk/browser/searchpos.ml | 6 | ||||
-rw-r--r-- | otherlibs/labltk/browser/shell.ml | 4 | ||||
-rw-r--r-- | otherlibs/labltk/browser/typecheck.ml | 2 | ||||
-rw-r--r-- | otherlibs/labltk/browser/viewer.ml | 2 |
8 files changed, 51 insertions, 51 deletions
diff --git a/otherlibs/labltk/browser/editor.ml b/otherlibs/labltk/browser/editor.ml index 773f71b0a..5174493a3 100644 --- a/otherlibs/labltk/browser/editor.ml +++ b/otherlibs/labltk/browser/editor.ml @@ -200,7 +200,7 @@ let send_phrase txt = sh#send ";;\n" let search_pos_window txt ~x ~y = - if txt.structure = [] & txt.psignature = [] then () else + if txt.structure = [] && txt.psignature = [] then () else let `Linechar (l, c) = Text.index txt.tw ~index:(`Atxy(x,y), []) in let text = Jg_text.get_all txt.tw in let pos = Searchpos.lines_to_chars l ~text + c in @@ -217,7 +217,7 @@ let search_pos_window txt ~x ~y = with Not_found -> () let search_pos_menu txt ~x ~y = - if txt.structure = [] & txt.psignature = [] then () else + if txt.structure = [] && txt.psignature = [] then () else let `Linechar (l, c) = Text.index txt.tw ~index:(`Atxy(x,y), []) in let text = Jg_text.get_all txt.tw in let pos = Searchpos.lines_to_chars l ~text + c in @@ -326,8 +326,8 @@ class editor ~top ~menus = object (self) bind tw ~events:[`Modified([`Alt], `KeyPress)] ~action:ignore; bind tw ~events:[`KeyPress] ~fields:[`Char] ~action:(fun ev -> - if ev.ev_Char <> "" & - (ev.ev_Char.[0] >= ' ' or + if ev.ev_Char <> "" && + (ev.ev_Char.[0] >= ' ' || List.mem ev.ev_Char.[0] (List.map ~f:control ['d'; 'h'; 'i'; 'k'; 'o'; 't'; 'w'; 'y'])) then Textvariable.set txt.modified "modified"); @@ -440,7 +440,7 @@ class editor ~top ~menus = object (self) close_in file; Text.mark_set tw ~mark:"insert" ~index; Text.see tw ~index; - if Filename.check_suffix name ".ml" or + if Filename.check_suffix name ".ml" || Filename.check_suffix name ".mli" then begin if !lex_on_load then self#lex (); diff --git a/otherlibs/labltk/browser/fileselect.ml b/otherlibs/labltk/browser/fileselect.ml index 4ddb7718f..0b513584f 100644 --- a/otherlibs/labltk/browser/fileselect.ml +++ b/otherlibs/labltk/browser/fileselect.ml @@ -70,7 +70,7 @@ let unix_regexp s = Str.regexp s let exact_match s ~pat = - Str.string_match ~pat s ~pos:0 & Str.match_end () = String.length s + Str.string_match ~pat s ~pos:0 && Str.match_end () = String.length s let ls ~dir ~pattern = let files = get_files_in_directory dir in @@ -117,16 +117,16 @@ let f ~title ~action:proc ?(dir = Unix.getcwd ()) else filter in let dir, pattern = parse_filter filter in - let dir = if !load_in_path & usepath then "" else + let dir = if !load_in_path && usepath then "" else (current_dir := Filename.dirname dir; dir) and pattern = if pattern = "" then "*" else pattern in current_pattern := pattern; let filter = - if !load_in_path & usepath then pattern else dir ^ pattern in + if !load_in_path && usepath then pattern else dir ^ pattern in let directories = get_directories_in_files ~path:dir (get_files_in_directory dir) in let matched_files = (* get matched file by subshell call. *) - if !load_in_path & usepath then + if !load_in_path && usepath then List.fold_left !Config.load_path ~init:[] ~f: begin fun acc dir -> let files = ls ~dir ~pattern in @@ -143,7 +143,7 @@ let f ~title ~action:proc ?(dir = Unix.getcwd ()) Listbox.delete filter_listbox ~first:(`Num 0) ~last:`End; Listbox.insert filter_listbox ~index:`End ~texts:matched_files; Jg_box.recenter filter_listbox ~index:(`Num 0); - if !load_in_path & usepath then + if !load_in_path && usepath then Listbox.configure directory_listbox ~takefocus:false else begin @@ -159,7 +159,7 @@ let f ~title ~action:proc ?(dir = Unix.getcwd ()) Grab.release tl; destroy tl; let l = - if !load_in_path & usepath then + if !load_in_path && usepath then List.fold_right l ~init:[] ~f: begin fun name acc -> if not (Filename.is_implicit name) then @@ -236,7 +236,7 @@ let f ~title ~action:proc ?(dir = Unix.getcwd ()) ~action:(fun ev -> let name = Listbox.get filter_listbox ~index:(Listbox.nearest filter_listbox ~y:ev.ev_MouseY) in - if !load_in_path & usepath then + if !load_in_path && usepath then try Textvariable.set selection_var (search_in_path ~name) with Not_found -> () else Textvariable.set selection_var (!current_dir ^ "/" ^ name)); @@ -279,7 +279,7 @@ let f ~title ~action:proc ?(dir = Unix.getcwd ()) pack [okb; flb; ccb] ~side:`Left ~fill:`X ~expand:true; pack [cfrm] ~before:frm ~side:`Bottom ~fill:`X; - if !load_in_path & usepath then begin + if !load_in_path && usepath then begin load_in_path := false; Checkbutton.invoke toggle_in_path; Checkbutton.select toggle_in_path diff --git a/otherlibs/labltk/browser/jg_completion.ml b/otherlibs/labltk/browser/jg_completion.ml index 9217fcf45..1bdedede5 100644 --- a/otherlibs/labltk/browser/jg_completion.ml +++ b/otherlibs/labltk/browser/jg_completion.ml @@ -23,7 +23,7 @@ class completion ?nocase texts = object val mutable current = 0 method add c = prefix <- prefix ^ c; - while current < List.length texts - 1 & + while current < List.length texts - 1 && lt_string (List.nth texts current) prefix ?nocase do current <- current + 1 diff --git a/otherlibs/labltk/browser/searchid.ml b/otherlibs/labltk/browser/searchid.ml index 2ce0d1674..6f427c235 100644 --- a/otherlibs/labltk/browser/searchid.ml +++ b/otherlibs/labltk/browser/searchid.ml @@ -106,38 +106,38 @@ let rec equal ~prefix t1 t2 = and fields2 = filter_row_fields false row1.row_fields in let r1, r2, pairs = merge_row_fields fields1 fields2 in - row1.row_closed = row2.row_closed & r1 = [] & r2 = [] & + row1.row_closed = row2.row_closed && r1 = [] && r2 = [] && List.for_all pairs ~f: begin fun (_,f1,f2) -> match row_field_repr f1, row_field_repr f2 with Rpresent None, Rpresent None -> true | Rpresent(Some t1), Rpresent (Some t2) -> equal t1 t2 ~prefix | Reither(c1, tl1, _), Reither(c2, tl2, _) -> - c1 = c2 & List.length tl1 = List.length tl2 & + c1 = c2 && List.length tl1 = List.length tl2 && List.for_all2 tl1 tl2 ~f:(equal ~prefix) | _ -> false end | Tarrow _, Tarrow _ -> let l1, t1 = all_args t1 and l2, t2 = all_args t2 in - equal t1 t2 ~prefix & - List.length l1 = List.length l2 & + equal t1 t2 ~prefix && + List.length l1 = List.length l2 && List.exists (permutations l1) ~f: begin fun l1 -> List.for_all2 l1 l2 ~f: begin fun (p1,t1) (p2,t2) -> - (p1 = "" or p1 = p2) & equal t1 t2 ~prefix + (p1 = "" || p1 = p2) && equal t1 t2 ~prefix end end | Ttuple l1, Ttuple l2 -> - List.length l1 = List.length l2 & + List.length l1 = List.length l2 && List.for_all2 l1 l2 ~f:(equal ~prefix) | Tconstr (p1, l1, _), Tconstr (p2, l2, _) -> remove_prefix ~prefix (longident_of_path p1) = (longident_of_path p2) - & List.length l1 = List.length l2 - & List.for_all2 l1 l2 ~f:(equal ~prefix) + && List.length l1 = List.length l2 + && List.for_all2 l1 l2 ~f:(equal ~prefix) | _ -> false -let is_opt s = s <> "" & s.[0] = '?' +let is_opt s = s <> "" && s.[0] = '?' let get_options = List.filter ~f:is_opt let rec included ~prefix t1 t2 = @@ -149,37 +149,37 @@ let rec included ~prefix t1 t2 = and fields2 = filter_row_fields false row1.row_fields in let r1, r2, pairs = merge_row_fields fields1 fields2 in - r1 = [] & + r1 = [] && List.for_all pairs ~f: begin fun (_,f1,f2) -> match row_field_repr f1, row_field_repr f2 with Rpresent None, Rpresent None -> true | Rpresent(Some t1), Rpresent (Some t2) -> included t1 t2 ~prefix | Reither(c1, tl1, _), Reither(c2, tl2, _) -> - c1 = c2 & List.length tl1 = List.length tl2 & + c1 = c2 && List.length tl1 = List.length tl2 && List.for_all2 tl1 tl2 ~f:(included ~prefix) | _ -> false end | Tarrow _, Tarrow _ -> let l1, t1 = all_args t1 and l2, t2 = all_args t2 in - included t1 t2 ~prefix & + included t1 t2 ~prefix && let len1 = List.length l1 and len2 = List.length l2 in let l2 = if arr len1 ~card:len2 < 100 then l2 else let ll1 = get_options (fst (List.split l1)) in List.filter l2 - ~f:(fun (l,_) -> not (is_opt l) or List.mem l ll1) + ~f:(fun (l,_) -> not (is_opt l) || List.mem l ll1) in - len1 <= len2 & + len1 <= len2 && List.exists (List2.flat_map ~f:permutations (choose len1 ~card:l2)) ~f: begin fun l2 -> List.for_all2 l1 l2 ~f: begin fun (p1,t1) (p2,t2) -> - (p1 = "" or p1 = p2) & included t1 t2 ~prefix + (p1 = "" || p1 = p2) && included t1 t2 ~prefix end end | Ttuple l1, Ttuple l2 -> let len1 = List.length l1 in - len1 <= List.length l2 & + len1 <= List.length l2 && List.exists (List2.flat_map ~f:permutations (choose len1 ~card:l2)) ~f: begin fun l2 -> List.for_all2 l1 l2 ~f:(included ~prefix) @@ -187,8 +187,8 @@ let rec included ~prefix t1 t2 = | _, Ttuple _ -> included (newty (Ttuple [t1])) t2 ~prefix | Tconstr (p1, l1, _), Tconstr (p2, l2, _) -> remove_prefix ~prefix (longident_of_path p1) = (longident_of_path p2) - & List.length l1 = List.length l2 - & List.for_all2 l1 l2 ~f:(included ~prefix) + && List.length l1 = List.length l2 + && List.for_all2 l1 l2 ~f:(included ~prefix) | _ -> false let mklid = function @@ -223,7 +223,7 @@ let rec search_type_in_signature t ~sign ~prefix ~mode = begin match td.type_manifest with None -> false | Some t -> matches t - end or + end || begin match td.type_kind with Type_abstract -> false | Type_variant l -> @@ -244,14 +244,14 @@ let rec search_type_in_signature t ~sign ~prefix ~mode = | Tsig_class (id, cl) -> let self = self_type cl.cty_type in if matches self - or (match cl.cty_new with None -> false | Some ty -> matches ty) - (* or List.exists (get_fields ~prefix ~sign self) + || (match cl.cty_new with None -> false | Some ty -> matches ty) + (* || List.exists (get_fields ~prefix ~sign self) ~f:(fun (_,_,ty_field) -> matches ty_field) *) then [lid_of_id id, Pclass] else [] | Tsig_cltype (id, cl) -> let self = self_type cl.clty_type in if matches self - (* or List.exists (get_fields ~prefix ~sign self) + (* || List.exists (get_fields ~prefix ~sign self) ~f:(fun (_,_,ty_field) -> matches ty_field) *) then [lid_of_id id, Pclass] else [] end @@ -323,7 +323,7 @@ let rec check_match ~pattern s = match pattern, s with [], [] -> true | '*'::l, l' -> check_match ~pattern:l l' - or check_match ~pattern:('?'::'*'::l) l' + || check_match ~pattern:('?'::'*'::l) l' | '?'::l, _::l' -> check_match ~pattern:l l' | x::l, y::l' when x == y -> check_match ~pattern:l l' | _ -> false @@ -344,12 +344,12 @@ let search_pattern_symbol text = | Tsig_module (i, _) when check i -> [i, Pmodule] | Tsig_modtype (i, _) when check i -> [i, Pmodtype] | Tsig_class (i, cl) when check i - or List.exists + || List.exists (get_fields ~prefix:[modname] ~sign (self_type cl.cty_type)) ~f:(fun (name,_,_) -> check_match ~pattern (explode name)) -> [i, Pclass] | Tsig_cltype (i, cl) when check i - or List.exists + || List.exists (get_fields ~prefix:[modname] ~sign (self_type cl.clty_type)) ~f:(fun (name,_,_) -> check_match ~pattern (explode name)) -> [i, Pcltype] @@ -367,7 +367,7 @@ let search_pattern_symbol text = (* let is_pattern s = try for i = 0 to String.length s -1 do - if s.[i] = '?' or s.[i] = '*' then raise Exit + if s.[i] = '?' || s.[i] = '*' then raise Exit done; false with Exit -> true *) @@ -446,13 +446,13 @@ let search_structure str ~name ~kind ~prefix = | Pstr_exception (s, _) when kind = Pconstructor -> name = s | Pstr_module (s, _) when kind = Pmodule -> name = s | Pstr_modtype (s, _) when kind = Pmodtype -> name = s - | Pstr_class l when kind = Pclass or kind = Ptype or kind = Pcltype -> + | Pstr_class l when kind = Pclass || kind = Ptype || kind = Pcltype -> List.iter l ~f: begin fun c -> if c.pci_name = name then loc := c.pci_loc.loc_start end; false - | Pstr_class_type l when kind = Pcltype or kind = Ptype -> + | Pstr_class_type l when kind = Pcltype || kind = Ptype -> List.iter l ~f: begin fun c -> if c.pci_name = name then loc := c.pci_loc.loc_start @@ -495,13 +495,13 @@ let search_signature sign ~name ~kind ~prefix = | Psig_exception (s, _) when kind = Pconstructor -> name = s | Psig_module (s, _) when kind = Pmodule -> name = s | Psig_modtype (s, _) when kind = Pmodtype -> name = s - | Psig_class l when kind = Pclass or kind = Ptype or kind = Pcltype -> + | Psig_class l when kind = Pclass || kind = Ptype || kind = Pcltype -> List.iter l ~f: begin fun c -> if c.pci_name = name then loc := c.pci_loc.loc_start end; false - | Psig_class_type l when kind = Ptype or kind = Pcltype -> + | Psig_class_type l when kind = Ptype || kind = Pcltype -> List.iter l ~f: begin fun c -> if c.pci_name = name then loc := c.pci_loc.loc_start diff --git a/otherlibs/labltk/browser/searchpos.ml b/otherlibs/labltk/browser/searchpos.ml index 3950e2b25..e887c3c10 100644 --- a/otherlibs/labltk/browser/searchpos.ml +++ b/otherlibs/labltk/browser/searchpos.ml @@ -31,12 +31,12 @@ let (~!) = Jg_memo.fast ~f:Str.regexp let lines_to_chars n ~text:s = let l = String.length s in let rec ltc n ~pos = - if n = 1 or pos >= l then pos else + if n = 1 || pos >= l then pos else if s.[pos] = '\n' then ltc (n-1) ~pos:(pos+1) else ltc n ~pos:(pos+1) in ltc n ~pos:0 let in_loc loc ~pos = - pos >= loc.loc_start & pos < loc.loc_end + pos >= loc.loc_start && pos < loc.loc_end let rec string_of_longident = function Lident s -> s @@ -457,7 +457,7 @@ and view_decl_menu lid ~kind ~env ~parent = Menu.add_command menu ~label ~command:(fun () -> view_decl lid ~kind ~env); end; - if kind = `Type or kind = `Modtype then begin + if kind = `Type || kind = `Modtype then begin let buf = new buffer ~size:60 in let (fo,ff) = Format.get_formatter_output_functions () and margin = Format.get_margin () in diff --git a/otherlibs/labltk/browser/shell.ml b/otherlibs/labltk/browser/shell.ml index b98a588d4..30870cf98 100644 --- a/otherlibs/labltk/browser/shell.ml +++ b/otherlibs/labltk/browser/shell.ml @@ -143,7 +143,7 @@ object (self) self#lex ~start:(idx,[`Linestart]) (); Text.see textw ~index:(`Mark"insert",[]) method private keypress c = - if not reading & c > " " then begin + if not reading && c > " " then begin reading <- true; Text.mark_set textw ~mark:"input" ~index:(`Mark"insert",[`Char(-1)]) end @@ -330,7 +330,7 @@ let f ~prog ~title = if l = [] then () else let name = List.hd l in current_dir := Filename.dirname name; - if Filename.check_suffix name ".cmo" or + if Filename.check_suffix name ".cmo" || Filename.check_suffix name ".cma" then let cmd = "#load \"" ^ name ^ "\";;\n" in diff --git a/otherlibs/labltk/browser/typecheck.ml b/otherlibs/labltk/browser/typecheck.ml index 8e1f62018..87a68a8c5 100644 --- a/otherlibs/labltk/browser/typecheck.ml +++ b/otherlibs/labltk/browser/typecheck.ml @@ -96,7 +96,7 @@ let f txt = Jg_text.tag_and_see txt.tw ~start:(tpos s) ~stop:(tpos e) ~tag:"error" end; end_message (); - if !nowarnings or Text.index ew ~index:tend = `Linechar (2,0) + if !nowarnings || Text.index ew ~index:tend = `Linechar (2,0) then destroy tl else begin error_messages := tl :: !error_messages; diff --git a/otherlibs/labltk/browser/viewer.ml b/otherlibs/labltk/browser/viewer.ml index ca7fe5101..c793c0bdf 100644 --- a/otherlibs/labltk/browser/viewer.ml +++ b/otherlibs/labltk/browser/viewer.ml @@ -290,7 +290,7 @@ let f ?(dir=Unix.getcwd()) ?on () = let s = Entry.get ew in let is_type = ref false and is_long = ref false in for i = 0 to String.length s - 2 do - if s.[i] = '-' & s.[i+1] = '>' then is_type := true; + if s.[i] = '-' && s.[i+1] = '>' then is_type := true; if s.[i] = '.' then is_long := true done; let l = |