Fix PR#6293
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14400 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
3b4d7cf63b
commit
950be999e6
1
Changes
1
Changes
|
@ -50,6 +50,7 @@ Bug fixes:
|
|||
- PR#6116: more efficient implementation of Digest.to_hex (patch by ygrek)
|
||||
- PR#6174: OCaml compiler loops on an example using GADTs (-rectypes case)
|
||||
- PR#6262: equality of first-class modules take module aliases into account
|
||||
- PR#6293: Assert_failure with invalid package type
|
||||
|
||||
Standard library:
|
||||
- PR#4986: add List.sort_uniq and Set.of_list
|
||||
|
|
|
@ -1946,6 +1946,10 @@ and type_expect_ ?in_function env sexp ty_expected =
|
|||
Texp_ident(path, lid, desc)
|
||||
| Val_unbound ->
|
||||
raise(Error(loc, env, Masked_instance_variable lid.txt))
|
||||
(*| Val_prim _ ->
|
||||
let p = Env.normalize_path (Some loc) env path in
|
||||
Env.add_required_global (Path.head p);
|
||||
Texp_ident(path, lid, desc)*)
|
||||
| _ ->
|
||||
Texp_ident(path, lid, desc)
|
||||
end;
|
||||
|
|
|
@ -1135,7 +1135,8 @@ let transl_with_constraint env id row_path orig_decl sdecl =
|
|||
let decl =
|
||||
{ type_params = params;
|
||||
type_arity = List.length params;
|
||||
type_kind = if arity_ok then orig_decl.type_kind else Type_abstract;
|
||||
type_kind =
|
||||
if arity_ok && man <> None then orig_decl.type_kind else Type_abstract;
|
||||
type_private = priv;
|
||||
type_manifest = man;
|
||||
type_variance = [];
|
||||
|
|
|
@ -1098,8 +1098,9 @@ and type_structure ?(toplevel = false) funct_body anchor env sstr scope =
|
|||
| Pstr_value(rec_flag, sdefs) ->
|
||||
let scope =
|
||||
match rec_flag with
|
||||
| Recursive -> Some (Annot.Idef {scope with
|
||||
Location.loc_start = loc.Location.loc_start})
|
||||
| Recursive ->
|
||||
Some (Annot.Idef {scope with
|
||||
Location.loc_start = loc.Location.loc_start})
|
||||
| Nonrecursive ->
|
||||
let start =
|
||||
match srem with
|
||||
|
|
|
@ -221,7 +221,8 @@ let create_package_mty fake loc env (p, l) =
|
|||
ptype_manifest = if fake then None else Some t;
|
||||
ptype_attributes = [];
|
||||
ptype_loc = loc} in
|
||||
Ast_helper.Mty.mk ~loc (Pmty_with (mty, [ Pwith_type ({ txt = s.txt; loc }, d) ]))
|
||||
Ast_helper.Mty.mk ~loc
|
||||
(Pmty_with (mty, [ Pwith_type ({ txt = s.txt; loc }, d) ]))
|
||||
)
|
||||
(Ast_helper.Mty.mk ~loc (Pmty_ident p))
|
||||
l
|
||||
|
|
Loading…
Reference in New Issue