summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--ocamldoc/odoc_merge.ml4
-rw-r--r--typing/typecore.ml16
2 files changed, 12 insertions, 8 deletions
diff --git a/ocamldoc/odoc_merge.ml b/ocamldoc/odoc_merge.ml
index 114a21e76..216102dc2 100644
--- a/ocamldoc/odoc_merge.ml
+++ b/ocamldoc/odoc_merge.ml
@@ -529,7 +529,7 @@ let rec merge_module_types merge_options mli ml =
Element_module m2 ->
if m2.m_name = m.m_name then
(
- merge_modules merge_options m m2 ;
+ ignore (merge_modules merge_options m m2);
(*
m.m_info <- merge_info_opt merge_options m.m_info m2.m_info;
m.m_loc <- { m.m_loc with loc_impl = m2.m_loc.loc_impl } ;
@@ -772,7 +772,7 @@ and merge_modules merge_options mli ml =
Element_module m2 ->
if m2.m_name = m.m_name then
(
- merge_modules merge_options m m2 ;
+ ignore (merge_modules merge_options m m2);
(*
m.m_info <- merge_info_opt merge_options m.m_info m2.m_info;
m.m_loc <- { m.m_loc with loc_impl = m2.m_loc.loc_impl } ;
diff --git a/typing/typecore.ml b/typing/typecore.ml
index d1b440cea..fe3500a60 100644
--- a/typing/typecore.ml
+++ b/typing/typecore.ml
@@ -841,11 +841,15 @@ let check_univars env kind exp ty_expected vars =
Less_general(kind, [ty, ty; ty_expected, ty_expected])))
(* Check that a type is not a function *)
-let check_partial_application env exp =
- match expand_head env exp.exp_type with
- | {desc = Tarrow _} ->
+let check_application_result env statement exp =
+ match (expand_head env exp.exp_type).desc with
+ | Tarrow _ ->
Location.prerr_warning exp.exp_loc Warnings.Partial_application
- | _ -> ()
+ | Tvar -> ()
+ | Tconstr (p, _, _) when Path.same p Predef.path_unit -> ()
+ | _ ->
+ if statement then
+ Location.prerr_warning exp.exp_loc Warnings.Statement_type
(* Hack to allow coercion of self. Will clean-up later. *)
let self_coercion = ref ([] : (Path.t * Location.t list ref) list)
@@ -1656,7 +1660,7 @@ and type_application env funct sargs =
| Tarrow _ ->
Location.prerr_warning exp.exp_loc Warnings.Partial_application
| Tvar ->
- add_delayed_check (fun () -> check_partial_application env exp)
+ add_delayed_check (fun () -> check_application_result env false exp)
| _ -> ()
end;
([Some exp, Required], ty_res)
@@ -1851,7 +1855,7 @@ and type_statement env sexp =
| Tvar when ty.level > tv.level ->
Location.prerr_warning sexp.pexp_loc Warnings.Nonreturning_statement
| Tvar ->
- add_delayed_check (fun () -> check_partial_application env exp)
+ add_delayed_check (fun () -> check_application_result env true exp)
| _ ->
Location.prerr_warning sexp.pexp_loc Warnings.Statement_type
end;