Skip to content

Commit

Permalink
ocaml#6387: allow attributes on variants in polymorphic variant types.
Browse files Browse the repository at this point in the history
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14712 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
alainfrisch committed Apr 30, 2014
1 parent 772a843 commit b791d66
Show file tree
Hide file tree
Showing 14 changed files with 27 additions and 22 deletions.
3 changes: 2 additions & 1 deletion parsing/ast_mapper.ml
Expand Up @@ -79,7 +79,8 @@ module T = struct
(* Type expressions for the core language *) (* Type expressions for the core language *)


let row_field sub = function let row_field sub = function
| Rtag (l, b, tl) -> Rtag (l, b, List.map (sub.typ sub) tl) | Rtag (l, attrs, b, tl) ->
Rtag (l, sub.attributes sub attrs, b, List.map (sub.typ sub) tl)
| Rinherit t -> Rinherit (sub.typ sub t) | Rinherit t -> Rinherit (sub.typ sub t)


let map sub {ptyp_desc = desc; ptyp_loc = loc; ptyp_attributes = attrs} = let map sub {ptyp_desc = desc; ptyp_loc = loc; ptyp_attributes = attrs} =
Expand Down
12 changes: 6 additions & 6 deletions parsing/parser.mly
Expand Up @@ -257,8 +257,8 @@ let varify_constructors var_names t =
{t with ptyp_desc = desc} {t with ptyp_desc = desc}
and loop_row_field = and loop_row_field =
function function
| Rtag(label,flag,lst) -> | Rtag(label,attrs,flag,lst) ->
Rtag(label,flag,List.map loop lst) Rtag(label,attrs,flag,List.map loop lst)
| Rinherit t -> | Rinherit t ->
Rinherit (loop t) Rinherit (loop t)
in in
Expand Down Expand Up @@ -1777,10 +1777,10 @@ row_field:
| simple_core_type { Rinherit $1 } | simple_core_type { Rinherit $1 }
; ;
tag_field: tag_field:
name_tag OF opt_ampersand amper_type_list name_tag attributes OF opt_ampersand amper_type_list
{ Rtag ($1, $3, List.rev $4) } { Rtag ($1, $2, $4, List.rev $5) }
| name_tag | name_tag attributes
{ Rtag ($1, true, []) } { Rtag ($1, $2, true, []) }
; ;
opt_ampersand: opt_ampersand:
AMPERSAND { true } AMPERSAND { true }
Expand Down
4 changes: 3 additions & 1 deletion parsing/parsetree.mli
Expand Up @@ -115,7 +115,7 @@ and package_type = Longident.t loc * (Longident.t loc * core_type) list
*) *)


and row_field = and row_field =
| Rtag of label * bool * core_type list | Rtag of label * attributes * bool * core_type list
(* [`A] ( true, [] ) (* [`A] ( true, [] )
[`A of T] ( false, [T] ) [`A of T] ( false, [T] )
[`A of T1 & .. & Tn] ( false, [T1;...Tn] ) [`A of T1 & .. & Tn] ( false, [T1;...Tn] )
Expand All @@ -125,6 +125,8 @@ and row_field =
constant (empty) constructor. constant (empty) constructor.
- '&' occurs when several types are used for the same constructor - '&' occurs when several types are used for the same constructor
(see 4.2 in the manual) (see 4.2 in the manual)
- TODO: switch to a record representation, and keep location
*) *)
| Rinherit of core_type | Rinherit of core_type
(* [ T ] *) (* [ T ] *)
Expand Down
2 changes: 1 addition & 1 deletion parsing/pprintast.ml
Expand Up @@ -286,7 +286,7 @@ class printer ()= object(self:'self)
| Ptyp_variant (l, closed, low) -> | Ptyp_variant (l, closed, low) ->
let type_variant_helper f x = let type_variant_helper f x =
match x with match x with
| Rtag (l, _, ctl) -> pp f "@[<2>%a%a@]" self#string_quot l | Rtag (l, _attrs, _, ctl) -> pp f "@[<2>%a%a@]" self#string_quot l
(fun f l -> match l with (fun f l -> match l with
|[] -> () |[] -> ()
| _ -> pp f "@;of@;%a" | _ -> pp f "@;of@;%a"
Expand Down
3 changes: 2 additions & 1 deletion parsing/printast.ml
Expand Up @@ -823,8 +823,9 @@ and label_x_expression i ppf (l,e) =


and label_x_bool_x_core_type_list i ppf x = and label_x_bool_x_core_type_list i ppf x =
match x with match x with
Rtag (l, b, ctl) -> Rtag (l, attrs, b, ctl) ->
line i ppf "Rtag \"%s\" %s\n" l (string_of_bool b); line i ppf "Rtag \"%s\" %s\n" l (string_of_bool b);
attributes (i+1) ppf attrs;
list (i+1) core_type ppf ctl list (i+1) core_type ppf ctl
| Rinherit (ct) -> | Rinherit (ct) ->
line i ppf "Rinherit\n"; line i ppf "Rinherit\n";
Expand Down
2 changes: 1 addition & 1 deletion tools/depend.ml
Expand Up @@ -48,7 +48,7 @@ let rec add_type bv ty =
| Ptyp_alias(t, s) -> add_type bv t | Ptyp_alias(t, s) -> add_type bv t
| Ptyp_variant(fl, _, _) -> | Ptyp_variant(fl, _, _) ->
List.iter List.iter
(function Rtag(_,_,stl) -> List.iter (add_type bv) stl (function Rtag(_,_,_,stl) -> List.iter (add_type bv) stl
| Rinherit sty -> add_type bv sty) | Rinherit sty -> add_type bv sty)
fl fl
| Ptyp_poly(_, t) -> add_type bv t | Ptyp_poly(_, t) -> add_type bv t
Expand Down
2 changes: 1 addition & 1 deletion tools/tast_iter.ml
Expand Up @@ -302,7 +302,7 @@ let class_structure sub cs =


let row_field sub rf = let row_field sub rf =
match rf with match rf with
| Ttag (_label, _bool, list) -> List.iter (sub # core_type) list | Ttag (_label, _attrs, _bool, list) -> List.iter (sub # core_type) list
| Tinherit ct -> sub # core_type ct | Tinherit ct -> sub # core_type ct


let class_field sub cf = let class_field sub cf =
Expand Down
4 changes: 2 additions & 2 deletions tools/untypeast.ml
Expand Up @@ -554,8 +554,8 @@ and untype_class_structure cs =


and untype_row_field rf = and untype_row_field rf =
match rf with match rf with
Ttag (label, bool, list) -> Ttag (label, attrs, bool, list) ->
Rtag (label, bool, List.map untype_core_type list) Rtag (label, attrs, bool, List.map untype_core_type list)
| Tinherit ct -> Rinherit (untype_core_type ct) | Tinherit ct -> Rinherit (untype_core_type ct)


and untype_class_field cf = and untype_class_field cf =
Expand Down
3 changes: 2 additions & 1 deletion typing/printtyped.ml
Expand Up @@ -804,8 +804,9 @@ and ident_x_loc_x_expression_def i ppf (l,_, e) =


and label_x_bool_x_core_type_list i ppf x = and label_x_bool_x_core_type_list i ppf x =
match x with match x with
Ttag (l, b, ctl) -> Ttag (l, attrs, b, ctl) ->
line i ppf "Rtag \"%s\" %s\n" l (string_of_bool b); line i ppf "Rtag \"%s\" %s\n" l (string_of_bool b);
attributes (i+1) ppf attrs;
list (i+1) core_type ppf ctl list (i+1) core_type ppf ctl
| Tinherit (ct) -> | Tinherit (ct) ->
line i ppf "Rinherit\n"; line i ppf "Rinherit\n";
Expand Down
2 changes: 1 addition & 1 deletion typing/typedtree.ml
Expand Up @@ -361,7 +361,7 @@ and package_type = {
} }


and row_field = and row_field =
Ttag of label * bool * core_type list Ttag of label * attributes * bool * core_type list
| Tinherit of core_type | Tinherit of core_type


and value_description = and value_description =
Expand Down
2 changes: 1 addition & 1 deletion typing/typedtree.mli
Expand Up @@ -360,7 +360,7 @@ and package_type = {
} }


and row_field = and row_field =
Ttag of label * bool * core_type list Ttag of label * attributes * bool * core_type list
| Tinherit of core_type | Tinherit of core_type


and value_description = and value_description =
Expand Down
2 changes: 1 addition & 1 deletion typing/typedtreeIter.ml
Expand Up @@ -531,7 +531,7 @@ module MakeIterator(Iter : IteratorArgument) : sig


and iter_row_field rf = and iter_row_field rf =
match rf with match rf with
Ttag (label, bool, list) -> Ttag (label, _attrs, bool, list) ->
List.iter iter_core_type list List.iter iter_core_type list
| Tinherit ct -> iter_core_type ct | Tinherit ct -> iter_core_type ct


Expand Down
4 changes: 2 additions & 2 deletions typing/typedtreeMap.ml
Expand Up @@ -576,8 +576,8 @@ module MakeMap(Map : MapArgument) = struct


and map_row_field rf = and map_row_field rf =
match rf with match rf with
Ttag (label, bool, list) -> Ttag (label, attrs, bool, list) ->
Ttag (label, bool, List.map map_core_type list) Ttag (label, attrs, bool, List.map map_core_type list)
| Tinherit ct -> Tinherit (map_core_type ct) | Tinherit ct -> Tinherit (map_core_type ct)


and map_class_field cf = and map_class_field cf =
Expand Down
4 changes: 2 additions & 2 deletions typing/typetexp.ml
Expand Up @@ -508,7 +508,7 @@ let rec transl_type env policy styp =
Hashtbl.add hfields h (l,f) Hashtbl.add hfields h (l,f)
in in
let add_field = function let add_field = function
Rtag (l, c, stl) -> Rtag (l, attrs, c, stl) ->
name := None; name := None;
let tl = List.map (transl_type env policy) stl in let tl = List.map (transl_type env policy) stl in
let f = match present with let f = match present with
Expand All @@ -523,7 +523,7 @@ let rec transl_type env policy styp =
Rpresent (Some st.ctyp_type) Rpresent (Some st.ctyp_type)
in in
add_typed_field styp.ptyp_loc l f; add_typed_field styp.ptyp_loc l f;
Ttag (l,c,tl) Ttag (l,attrs,c,tl)
| Rinherit sty -> | Rinherit sty ->
let cty = transl_type env policy sty in let cty = transl_type env policy sty in
let ty = cty.ctyp_type in let ty = cty.ctyp_type in
Expand Down

0 comments on commit b791d66

Please sign in to comment.