diff options
author | Xavier Leroy <xavier.leroy@inria.fr> | 1999-02-24 15:21:50 +0000 |
---|---|---|
committer | Xavier Leroy <xavier.leroy@inria.fr> | 1999-02-24 15:21:50 +0000 |
commit | 5038f3cdb6377dfc84e4642b710c1a1949060e1d (patch) | |
tree | 5d40d3f38506e477142555e1a22fa860236f566c | |
parent | 6fb83c93fcf5a7687ebaf084daf3933ff23c22e9 (diff) |
Ajout de Pervasives.ignore. List.remove -> List.remove_ass*
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2304 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
38 files changed, 90 insertions, 70 deletions
diff --git a/asmcomp/cmmgen.ml b/asmcomp/cmmgen.ml index 77c13b4de..3e36407a7 100644 --- a/asmcomp/cmmgen.ml +++ b/asmcomp/cmmgen.ml @@ -483,6 +483,8 @@ let rec transl = function (* Primitives *) | Uprim(Pidentity, [arg]) -> transl arg + | Uprim(Pignore, [arg]) -> + return_unit(transl arg) | Uprim(Pgetglobal id, []) -> Cconst_symbol(Ident.name id) diff --git a/asmcomp/selectgen.ml b/asmcomp/selectgen.ml index f072612ef..7c063087e 100644 --- a/asmcomp/selectgen.ml +++ b/asmcomp/selectgen.ml @@ -500,7 +500,7 @@ method emit_expr env exp = alloc_state <- None; rd | Some(ralloc, ofs) -> - self#insert_op (Iintop_imm(Iadd, ofs)) ralloc rd; + ignore(self#insert_op (Iintop_imm(Iadd, ofs)) ralloc rd); alloc_state <- Some(ralloc, ofs + size); self#emit_stores env new_args ralloc (Arch.offset_addressing header_addressing ofs); @@ -512,7 +512,7 @@ method emit_expr env exp = self#insert_op op r1 rd end | Csequence(e1, e2) -> - let _ = self#emit_expr env e1 in + ignore(self#emit_expr env e1); self#emit_expr env e2 | Cifthenelse(econd, eif, eelse) -> let (cond, earg) = self#select_condition econd in @@ -688,7 +688,7 @@ method emit_tail env exp = self#insert (Iop Imove) r1 rd; self#insert Iraise rd [||] | Csequence(e1, e2) -> - let _ = self#emit_expr env e1 in + ignore(self#emit_expr env e1); self#emit_tail env e2 | Cifthenelse(econd, eif, eelse) -> let (cond, earg) = self#select_condition econd in diff --git a/bytecomp/bytegen.ml b/bytecomp/bytegen.ml index 9ecf54d9f..0502aa15d 100644 --- a/bytecomp/bytegen.ml +++ b/bytecomp/bytegen.ml @@ -336,6 +336,8 @@ let rec comp_expr env exp sz cont = end | Lprim(Pidentity, [arg]) -> comp_expr env arg sz cont + | Lprim(Pignore, [arg]) -> + comp_expr env arg sz (add_const_unit cont) | Lprim(Pnot, [arg]) -> let newcont = match cont with diff --git a/bytecomp/lambda.ml b/bytecomp/lambda.ml index 231962121..64b14e3ac 100644 --- a/bytecomp/lambda.ml +++ b/bytecomp/lambda.ml @@ -17,6 +17,7 @@ open Asttypes type primitive = Pidentity + | Pignore (* Globals *) | Pgetglobal of Ident.t | Psetglobal of Ident.t diff --git a/bytecomp/lambda.mli b/bytecomp/lambda.mli index 847543936..5302f228d 100644 --- a/bytecomp/lambda.mli +++ b/bytecomp/lambda.mli @@ -17,6 +17,7 @@ open Asttypes type primitive = Pidentity + | Pignore (* Globals *) | Pgetglobal of Ident.t | Psetglobal of Ident.t diff --git a/bytecomp/printlambda.ml b/bytecomp/printlambda.ml index f8564dc9a..cdf4be787 100644 --- a/bytecomp/printlambda.ml +++ b/bytecomp/printlambda.ml @@ -53,6 +53,7 @@ let rec structured_constant = function let primitive = function Pidentity -> print_string "id" + | Pignore -> print_string "ignore" | Pgetglobal id -> print_string "global "; Ident.print id | Psetglobal id -> print_string "setglobal "; Ident.print id | Pmakeblock(tag, Immutable) -> print_string "makeblock "; print_int tag diff --git a/bytecomp/symtable.ml b/bytecomp/symtable.ml index b712282dc..b64b1fe3b 100644 --- a/bytecomp/symtable.ml +++ b/bytecomp/symtable.ml @@ -73,8 +73,7 @@ let slot_for_literal cst = let c_prim_table = ref(empty_numtable : string numtable) let set_prim_table name = - let _ = enter_numtable c_prim_table name in - () + ignore(enter_numtable c_prim_table name) let num_of_prim name = try @@ -85,7 +84,7 @@ let num_of_prim name = else raise(Error(Unavailable_primitive name)) let require_primitive name = - if name.[0] <> '%' then begin let _ = num_of_prim name in () end + if name.[0] <> '%' then ignore(num_of_prim name) let all_primitives () = let prim = Array.create !c_prim_table.num_cnt "" in diff --git a/bytecomp/translcore.ml b/bytecomp/translcore.ml index a6c7142c2..15395e210 100644 --- a/bytecomp/translcore.ml +++ b/bytecomp/translcore.ml @@ -85,6 +85,7 @@ let comparisons_table = create_hashtable 11 [ let primitives_table = create_hashtable 31 [ "%identity", Pidentity; + "%ignore", Pignore; "%field0", Pfield 0; "%field1", Pfield 1; "%setfield0", Psetfield(0, true); diff --git a/byterun/callback.c b/byterun/callback.c index f8535caab..1e7883551 100644 --- a/byterun/callback.c +++ b/byterun/callback.c @@ -52,7 +52,6 @@ static void thread_callback(void) value callbackN_exn(value closure, int narg, value args[]) { - value res; int i; Assert(narg + 4 <= 256); diff --git a/debugger/command_line.ml b/debugger/command_line.ml index bd8962d7f..43fcd1b6d 100644 --- a/debugger/command_line.ml +++ b/debugger/command_line.ml @@ -215,7 +215,7 @@ let instr_cd lexbuf = let instr_pwd lexbuf = eol lexbuf; - let _ = system "/bin/pwd" in () + ignore(system "/bin/pwd") let instr_dir lexbuf = let new_directory = argument_list_eol argument lexbuf in diff --git a/debugger/debugcom.ml b/debugger/debugcom.ml index ac8103294..e7a3e5043 100644 --- a/debugger/debugcom.ml +++ b/debugger/debugcom.ml @@ -119,7 +119,7 @@ let initial_frame () = (stack_pos, pc) let set_initial_frame () = - let _ = initial_frame () in () + ignore(initial_frame ()) (* Move up one frame *) (* Return stack position and current pc. diff --git a/debugger/frames.ml b/debugger/frames.ml index 5f4f92e18..d3a0cae53 100644 --- a/debugger/frames.ml +++ b/debugger/frames.ml @@ -114,7 +114,7 @@ let do_backtrace action = event := any_event_at_pc pc done with Exit -> () - | Not_found -> let _ = action None in () + | Not_found -> ignore (action None) end; set_frame initial_sp diff --git a/debugger/history.ml b/debugger/history.ml index 22dcd35ab..bef338399 100644 --- a/debugger/history.ml +++ b/debugger/history.ml @@ -39,4 +39,4 @@ let previous_time_1 () = let rec previous_time n = if n = 1 then previous_time_1() - else begin let _ = previous_time_1() in previous_time(n-1) end + else begin ignore(previous_time_1()); previous_time(n-1) end diff --git a/debugger/loadprinter.ml b/debugger/loadprinter.ml index 72d5f2523..aaf48a259 100644 --- a/debugger/loadprinter.ml +++ b/debugger/loadprinter.ml @@ -80,7 +80,7 @@ let loadfile name = Dynlink.add_interfaces stdlib_units [Config.standard_library]; Dynlink.allow_unsafe_modules true end; - let _ = loadfiles name in () + ignore(loadfiles name) (* Return the value referred to by a path (as in toplevel/topdirs) *) (* Note: evaluation proceeds in the debugger memory space, not in diff --git a/debugger/program_loading.ml b/debugger/program_loading.ml index 88b5128c4..9b1528335 100644 --- a/debugger/program_loading.ml +++ b/debugger/program_loading.ml @@ -51,8 +51,7 @@ let generic_exec cmdline = function () -> match fork () with 0 -> (* Try to detach the process from the controlling terminal, so that it does not receive SIGINT on ctrl-C. *) - begin try let _ = setsid() in () - with Invalid_argument _ -> () end; + begin try ignore(setsid()) with Invalid_argument _ -> () end; execv shell [| shell; "-c"; cmdline() |] | _ -> exit 0 with x -> diff --git a/debugger/show_source.ml b/debugger/show_source.ml index 5246e7c44..918e130dd 100644 --- a/debugger/show_source.ml +++ b/debugger/show_source.ml @@ -61,7 +61,7 @@ let show_point mdle point before selected = begin try let buffer = get_buffer mdle in let (start, line_number) = line_of_pos buffer point in - let _ = print_line buffer line_number start point before in () + ignore(print_line buffer line_number start point before) with Out_of_range -> (* line_of_pos *) prerr_endline "Position out of range." diff --git a/debugger/symbols.ml b/debugger/symbols.ml index c2737dd62..8f0c7c35e 100644 --- a/debugger/symbols.ml +++ b/debugger/symbols.ml @@ -115,7 +115,7 @@ let event_at_pc pc = | _ -> ev let set_event_at_pc pc = - try let _ = event_at_pc pc in Debugcom.set_event pc + try ignore(event_at_pc pc); Debugcom.set_event pc with Not_found -> () (* List all events in module *) diff --git a/debugger/time_travel.ml b/debugger/time_travel.ml index c5aa1a163..dc84ed7ef 100644 --- a/debugger/time_travel.ml +++ b/debugger/time_travel.ml @@ -524,7 +524,7 @@ let finish () = raise Toplevel end; begin - try let _ = Symbols.any_event_at_pc pc in () + try ignore(Symbols.any_event_at_pc pc) with Not_found -> prerr_endline "Calling function has no debugging information."; raise Toplevel diff --git a/otherlibs/dynlink/dynlink.ml b/otherlibs/dynlink/dynlink.ml index ae6c4e016..0ccf3e8f6 100644 --- a/otherlibs/dynlink/dynlink.ml +++ b/otherlibs/dynlink/dynlink.ml @@ -137,7 +137,7 @@ let load_compunit ic file_name compunit = raise(Error(Linking_error (file_name, new_error))) end; begin try - let _ = (Meta.reify_bytecode code code_size) () in () + ignore((Meta.reify_bytecode code code_size) ()) with exn -> Symtable.restore_state initial_symtable; raise exn diff --git a/otherlibs/threads/pervasives.ml b/otherlibs/threads/pervasives.ml index acd08d6ac..861ff0ab9 100644 --- a/otherlibs/threads/pervasives.ml +++ b/otherlibs/threads/pervasives.ml @@ -132,6 +132,10 @@ external unsafe_char_of_int : int -> char = "%identity" let char_of_int n = if n < 0 or n > 255 then invalid_arg "char_of_int" else unsafe_char_of_int n +(* Unit operations *) + +external ignore : 'a -> unit = "%ignore" + (* Pair operations *) external fst : 'a * 'b -> 'a = "%field0" diff --git a/otherlibs/threads/threadUnix.ml b/otherlibs/threads/threadUnix.ml index a20bdf876..17ab89bb2 100644 --- a/otherlibs/threads/threadUnix.ml +++ b/otherlibs/threads/threadUnix.ml @@ -22,17 +22,17 @@ open Unix Make sure we're not preempted just after disabling the timer... *) let execv proc args = Thread.critical_section := true; - let _ = Unix.setitimer ITIMER_VIRTUAL {it_interval = 0.0; it_value = 0.0} in + ignore(Unix.setitimer ITIMER_VIRTUAL {it_interval = 0.0; it_value = 0.0}); Unix.execv proc args let execve proc args env = Thread.critical_section := true; - let _ = Unix.setitimer ITIMER_VIRTUAL {it_interval = 0.0; it_value = 0.0} in + ignore(Unix.setitimer ITIMER_VIRTUAL {it_interval = 0.0; it_value = 0.0}); Unix.execve proc args env let execvp proc args = Thread.critical_section := true; - let _ = Unix.setitimer ITIMER_VIRTUAL {it_interval = 0.0; it_value = 0.0} in + ignore(Unix.setitimer ITIMER_VIRTUAL {it_interval = 0.0; it_value = 0.0}); Unix.execvp proc args let wait () = @@ -126,8 +126,7 @@ let connect s addr = with Unix_error((EINPROGRESS | EWOULDBLOCK | EAGAIN), _, _) -> Thread.wait_write s; (* Check if it really worked *) - let _ = Unix.getpeername s in - () + ignore(Unix.getpeername s) let rec recv fd buf ofs len flags = Thread.wait_read fd; @@ -178,6 +177,6 @@ let establish_server server_fun sockaddr = close_in inchan; close_out outchan; exit 0 - | id -> close s; let _ = waitpid [] id (* Reclaim the son *) in () + | id -> close s; ignore(waitpid [] id) (* Reclaim the son *) done diff --git a/stdlib/filename.ml b/stdlib/filename.ml index f3279c95f..6368b7f3a 100644 --- a/stdlib/filename.ml +++ b/stdlib/filename.ml @@ -65,9 +65,7 @@ let wnt_is_implicit n = && (String.length n < 3 || String.sub n 0 3 <> "..\\") ;; -let contains_colon n = - try let _ = String.index n ':' in true - with Not_found -> false +let contains_colon n = String.contains n ':' ;; let mac_is_relative n = diff --git a/stdlib/format.ml b/stdlib/format.ml index a05156c9c..d2fd62d74 100644 --- a/stdlib/format.ml +++ b/stdlib/format.ml @@ -303,7 +303,7 @@ let rec advance_left state = (size < 0 && (state.pp_right_total - state.pp_left_total < state.pp_space_left)) then begin - let _ = take_queue state.pp_queue in + ignore(take_queue state.pp_queue); format_pp_token state (if size < 0 then pp_infinity else size) tok; state.pp_left_total <- len + state.pp_left_total; advance_left state diff --git a/stdlib/list.ml b/stdlib/list.ml index 90cee4303..170b803d6 100644 --- a/stdlib/list.ml +++ b/stdlib/list.ml @@ -136,13 +136,13 @@ let rec mem_assq x = function | [] -> false | (a, b) :: l -> a == x || mem_assq x l -let rec remove x = function +let rec remove_assoc x = function | [] -> [] - | (a, b as pair) :: l -> if a = x then l else pair :: remove x l + | (a, b as pair) :: l -> if a = x then l else pair :: remove_assoc x l -let rec removeq x = function +let rec remove_assq x = function | [] -> [] - | (a, b as pair) :: l -> if a == x then l else pair :: removeq x l + | (a, b as pair) :: l -> if a == x then l else pair :: remove_assq x l let rec find p = function | [] -> raise Not_found @@ -154,6 +154,8 @@ let find_all p = | x :: l -> if p x then find (x :: accu) l else find accu l in find [] +let filter = find_all + let rec partition p l = let rec part yes no = function | [] -> (rev yes, rev no) diff --git a/stdlib/list.mli b/stdlib/list.mli index cdd92b8c6..fd8fd5049 100644 --- a/stdlib/list.mli +++ b/stdlib/list.mli @@ -107,15 +107,17 @@ val find : ('a -> bool) -> 'a list -> 'a Raise [Not_found] if there is no value that satisfies [p] in the list [l]. *) +val filter : ('a -> bool) -> 'a list -> 'a list val find_all : ('a -> bool) -> 'a list -> 'a list - (* [find_all p l] returns all the elements of the list [l] - that satisfies the predicate [p]. *) + (* [filter p l] returns all the elements of the list [l] + that satisfies the predicate [p]. [find_all] is another name + for [filter]. *) val partition : ('a -> bool) -> 'a list -> 'a list * 'a list - (* [partition p l] returns a pair of lists [(l1, l2)], such - that [l1] is the list of all the elements of [l] that - satisfy the predicate [p], and [l2] is the list of all the - elements of [l] that do not satisfy [p]. *) + (* [partition p l] returns a pair of lists [(l1, l2)], where + [l1] is the list of all the elements of [l] that + satisfy the predicate [p], and [l2] is the list of all the + elements of [l] that do not satisfy [p]. *) (** Association lists *) @@ -134,16 +136,16 @@ val mem_assoc : 'a -> ('a * 'b) list -> bool (* Same as [assoc], but simply return true if a binding exists, and false if no bindings exist for the given key. *) val mem_assq : 'a -> ('a * 'b) list -> bool - (* Same as [mem_assoc], but uses physical equality instead of structural - equality to compare keys. *) + (* Same as [mem_assoc], but uses physical equality instead of + structural equality to compare keys. *) -val remove : 'a -> ('a * 'b) list -> ('a * 'b) list - (* [remove a l] returns the list of +val remove_assoc : 'a -> ('a * 'b) list -> ('a * 'b) list + (* [remove_assoc a l] returns the list of pairs [l] without the first pair with key [a], if any. *) -val removeq : 'a -> ('a * 'b) list -> ('a * 'b) list - (* Same as [remove], but uses physical equality instead of structural - equality to compare keys. *) +val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list + (* Same as [remove_assq], but uses physical equality instead + of structural equality to compare keys. *) (** Lists of pairs *) diff --git a/stdlib/pervasives.ml b/stdlib/pervasives.ml index 37fbef982..ed24d2236 100644 --- a/stdlib/pervasives.ml +++ b/stdlib/pervasives.ml @@ -128,6 +128,10 @@ external unsafe_char_of_int : int -> char = "%identity" let char_of_int n = if n < 0 or n > 255 then invalid_arg "char_of_int" else unsafe_char_of_int n +(* Unit operations *) + +external ignore : 'a -> unit = "%ignore" + (* Pair operations *) external fst : 'a * 'b -> 'a = "%field0" @@ -264,12 +268,12 @@ let rec input_line chan = raise End_of_file else if n > 0 then begin (* n > 0: newline found in buffer *) let res = string_create (n-1) in - let _ = unsafe_input chan res 0 (n-1) in - let _ = input_char chan in (* skip the newline *) + ignore (unsafe_input chan res 0 (n-1)); + ignore (input_char chan); (* skip the newline *) res end else begin (* n < 0: newline not found *) let beg = string_create (-n) in - let _ = unsafe_input chan beg 0 (-n) in + ignore(unsafe_input chan beg 0 (-n)); try beg ^ input_line chan with End_of_file -> diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli index 28041b9c2..49bc3a2b2 100644 --- a/stdlib/pervasives.mli +++ b/stdlib/pervasives.mli @@ -302,6 +302,14 @@ val char_of_int : int -> char Raise [Invalid_argument "char_of_int"] if the argument is outside the range 0--255. *) +(*** Unit operations *) + +external ignore : 'a -> unit = "%ignore" + (* Discard the value of its argument and return [()]. + For instance, [ignore(f x)] discards the result of + the side-effecting function [f]. It is equivalent to + [f x; ()], except that no warning is generated. *) + (*** String conversion functions *) val string_of_bool : bool -> string diff --git a/stdlib/stream.ml b/stdlib/stream.ml index 1a707dec6..8b4dd6841 100644 --- a/stdlib/stream.ml +++ b/stdlib/stream.ml @@ -120,7 +120,7 @@ let empty s = let iter f strm = let rec do_rec () = match peek strm with - Some a -> junk strm; let _ = f a in do_rec () + Some a -> junk strm; ignore(f a); do_rec () | None -> () in do_rec () diff --git a/stdlib/string.ml b/stdlib/string.ml index ca32cc6e2..e07fd4b60 100644 --- a/stdlib/string.ml +++ b/stdlib/string.ml @@ -159,10 +159,10 @@ let rindex_from s i c = let contains_from s i c = if i < 0 || i >= length s then invalid_arg "String.contains_from" else - try let _ = index_rec s (length s) i c in true with Not_found -> false;; + try ignore(index_rec s (length s) i c); true with Not_found -> false;; let rcontains_from s i c = if i < 0 || i >= length s then invalid_arg "String.rcontains_from" else - try let _ = rindex_rec s i c in true with Not_found -> false;; + try ignore(rindex_rec s i c); true with Not_found -> false;; let contains s c = s <> "" && contains_from s 0 c;; diff --git a/stdlib/sys.ml b/stdlib/sys.ml index 23293a153..4bfc0c236 100644 --- a/stdlib/sys.ml +++ b/stdlib/sys.ml @@ -40,8 +40,7 @@ type signal_behavior = external signal: int -> signal_behavior -> signal_behavior = "install_signal_handler" -let set_signal sig_num sig_beh = - let _ = signal sig_num sig_beh in () +let set_signal sig_num sig_beh = ignore(signal sig_num sig_beh) let sigabrt = -1 let sigalrm = -2 diff --git a/toplevel/topdirs.ml b/toplevel/topdirs.ml index 57ea80430..3437f6897 100644 --- a/toplevel/topdirs.ml +++ b/toplevel/topdirs.ml @@ -68,7 +68,7 @@ let load_compunit ic filename compunit = Symtable.patch_object code compunit.cu_reloc; Symtable.update_global_table(); begin try - let _ = (Meta.reify_bytecode code code_size) () in () + ignore((Meta.reify_bytecode code code_size) ()) with exn -> Symtable.restore_state initial_symtable; print_exception_outcome exn; @@ -106,7 +106,7 @@ let _ = Hashtbl.add directive_table "load" (Directive_string dir_load) (* Load commands from a file *) -let dir_use name = let _ = Toploop.use_file name in () +let dir_use name = ignore(Toploop.use_file name) let _ = Hashtbl.add directive_table "use" (Directive_string dir_use) diff --git a/toplevel/toploop.ml b/toplevel/toploop.ml index e5619012a..4551f6465 100644 --- a/toplevel/toploop.ml +++ b/toplevel/toploop.ml @@ -208,7 +208,7 @@ let use_file name = (* Skip initial #! line if any *) let buffer = String.create 2 in if input ic buffer 0 2 = 2 && buffer = "#!" - then let _ = input_line ic in () + then ignore(input_line ic) else seek_in ic 0; let success = protect Location.input_name filename (fun () -> @@ -272,8 +272,7 @@ let _ = Compile.init_path() let load_ocamlinit () = - if Sys.file_exists ".ocamlinit" then let _ = use_silently ".ocamlinit" in () - + if Sys.file_exists ".ocamlinit" then ignore(use_silently ".ocamlinit") (* The interactive loop *) @@ -299,7 +298,7 @@ let loop() = Location.reset(); first_line := true; let phr = try !parse_toplevel_phrase lb with Exit -> raise PPerror in - let _ = execute_phrase true phr in () + ignore(execute_phrase true phr) with End_of_file -> exit 0 | Sys.Break -> diff --git a/typing/ctype.ml b/typing/ctype.ml index 91692ab6a..48b969906 100644 --- a/typing/ctype.ml +++ b/typing/ctype.ml @@ -1268,7 +1268,7 @@ let rec filter_method env name priv ty = raise (Unify []) let check_filter_method env name priv ty = - let _ = filter_method env name priv ty in () + ignore(filter_method env name priv ty) let filter_self_method env lab priv meths ty = let ty' = filter_method env lab priv ty in diff --git a/typing/includemod.ml b/typing/includemod.ml index ab834ef36..5ce2bfe70 100644 --- a/typing/includemod.ml +++ b/typing/includemod.ml @@ -289,7 +289,7 @@ and check_modtype_equiv env mty1 mty2 = let check_modtype_inclusion env mty1 mty2 = try - let _ = modtypes env Subst.identity mty1 mty2 in () + ignore(modtypes env Subst.identity mty1 mty2) with Error reasons -> raise Not_found diff --git a/typing/printtyp.ml b/typing/printtyp.ml index 13bbae353..07af1342e 100644 --- a/typing/printtyp.ml +++ b/typing/printtyp.ml @@ -76,10 +76,10 @@ let print_name_of_type t = print_string (name_of_type t) let check_name_of_type t = - let _ = name_of_type t in () + ignore(name_of_type t) let remove_name_of_type t = - names := List.removeq t !names + names := List.remove_assq t !names let visited_objects = ref ([] : type_expr list) let aliased = ref ([] : type_expr list) diff --git a/typing/typemod.ml b/typing/typemod.ml index 4f509ccb8..0794439d9 100644 --- a/typing/typemod.ml +++ b/typing/typemod.ml @@ -74,7 +74,7 @@ let merge_constraint initial_env loc sg lid constr = when Ident.name id = s -> let (path, mty') = type_module_path initial_env loc lid in let newmty = Mtype.strengthen env mty' path in - let _ = Includemod.modtypes env newmty mty in + ignore(Includemod.modtypes env newmty mty); Tsig_module(id, newmty) :: rem | (Tsig_module(id, mty) :: rem, s :: namelist, _) when Ident.name id = s -> let newsg = merge env (extract_sig env loc mty) namelist in diff --git a/typing/typetexp.ml b/typing/typetexp.ml index c0a587f04..4520d94c2 100644 --- a/typing/typetexp.ml +++ b/typing/typetexp.ml @@ -130,10 +130,11 @@ let rec transl_type env policy styp = let args = List.map (transl_type env policy) stl in let params = List.map (fun _ -> Ctype.newvar ()) args in let cstr = newty (Tconstr(path, params, ref Mnil)) in - let _ = - try Ctype.expand_head env cstr with Unify trace -> - raise (Error(styp.ptyp_loc, Type_mismatch trace)) - in + begin try + ignore(Ctype.expand_head env cstr) + with Unify trace -> + raise (Error(styp.ptyp_loc, Type_mismatch trace)) + end; List.iter2 (fun (sty, ty) ty' -> try unify env ty ty' with Unify trace -> diff --git a/utils/ccomp.ml b/utils/ccomp.ml index 70706f90a..d6dc6daf7 100644 --- a/utils/ccomp.ml +++ b/utils/ccomp.ml @@ -21,8 +21,7 @@ let command cmdline = end; Sys.command cmdline -let run_command cmdline = - let _ = command cmdline in () +let run_command cmdline = ignore(command cmdline) let compile_file name = command |