summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2005-03-24 12:19:54 +0000
committerDamien Doligez <damien.doligez-inria.fr>2005-03-24 12:19:54 +0000
commit6dea6b4af83a32d2d011d0e91f5fd557582a0cd0 (patch)
tree1e61df29ed032003387421396c93dc26c2f48907
parentef396b4e5a34ceb49efbbe39058746a68f5ab503 (diff)
meilleurs messages d'erreur pour let rec
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6822 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--typing/typecore.ml21
1 files changed, 17 insertions, 4 deletions
diff --git a/typing/typecore.ml b/typing/typecore.ml
index 21e42eea8..b5dd272fb 100644
--- a/typing/typecore.ml
+++ b/typing/typecore.ml
@@ -742,11 +742,20 @@ let type_format loc fmt =
(* Approximate the type of an expression, for better recursion *)
-let rec approx_type sty =
+let rec approx_type env sty =
match sty.ptyp_desc with
Ptyp_arrow (p, _, sty) ->
let ty1 = if is_optional p then type_option (newvar ()) else newvar () in
- newty (Tarrow (p, ty1, approx_type sty, Cok))
+ newty (Tarrow (p, ty1, approx_type env sty, Cok))
+ | Ptyp_tuple args ->
+ newty (Ttuple (List.map (approx_type env) args))
+ | Ptyp_constr (lid, ctl) ->
+ begin try
+ let tyl = List.map (approx_type env) ctl in
+ let (path, _) = Env.lookup_type lid env in
+ newconstr path tyl
+ with Not_found -> newvar ()
+ end
| _ -> newvar ()
let rec type_approx env sexp =
@@ -762,9 +771,13 @@ let rec type_approx env sexp =
| Pexp_ifthenelse (_,e,_) -> type_approx env e
| Pexp_sequence (_,e) -> type_approx env e
| Pexp_constraint (e, sty1, sty2) ->
+ let approx_ty_opt = function
+ | None -> newvar ()
+ | Some sty -> approx_type env sty
+ in
let ty = type_approx env e
- and ty1 = match sty1 with None -> newvar () | Some sty -> approx_type sty
- and ty2 = match sty2 with None -> newvar () | Some sty -> approx_type sty
+ and ty1 = approx_ty_opt sty1
+ and ty2 = approx_ty_opt sty2
in begin
try unify env ty ty1; unify env ty1 ty2; ty2
with Unify trace ->