Skip to content

Commit

Permalink
Support for constraints on parametrized types in package types.
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/fstclassmod_parametrized@10675 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
alainfrisch committed Sep 9, 2010
1 parent 0fe17f8 commit 3dadaef
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 2 deletions.
12 changes: 11 additions & 1 deletion typing/oprint.ml
Expand Up @@ -219,7 +219,17 @@ and print_simple_out_type ppf =
List.iter2
(fun s t ->
let sep = if !first then (first := false; "with") else "and" in
fprintf ppf " %s type %s = %a" sep s print_out_type t
match t with
| Otyp_poly (sl, t) ->
fprintf ppf " %s type " sep;
begin match sl with
| [] -> ()
| [x] -> fprintf ppf "'%s " x
| l -> fprintf ppf "(%a) " pr_vars l
end;
fprintf ppf "%s = %a" s print_out_type t
| _ ->
assert false
)
n tyl;
fprintf ppf ")@]"
Expand Down
4 changes: 3 additions & 1 deletion typing/typetexp.ml
Expand Up @@ -133,14 +133,16 @@ let transl_package_type fake loc env (p, l) transl =
List.map
(fun (_, c) ->
match c with
| Pwith_type {ptype_params = [];
| Pwith_type {ptype_params = params;
ptype_cstrs = [];
ptype_kind = Ptype_abstract;
ptype_private = Asttypes.Public;
ptype_manifest = Some t;
ptype_variance = variance;
ptype_loc = loc}
when List.for_all (function (false, false) -> true | _ -> false) variance ->
let t = {ptyp_desc = Ptyp_poly(params, t);
ptyp_loc = t.ptyp_loc} in
transl t
| Pwith_type {ptype_loc = loc}
| Pwith_typesubst {ptype_loc = loc} ->
Expand Down

0 comments on commit 3dadaef

Please sign in to comment.