Custom syntax for floating attributes: [@@@id].

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14588 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2014-04-14 14:42:41 +00:00
parent 5f5bd08abc
commit f31ba39923
3 changed files with 35 additions and 25 deletions

View File

@ -78,10 +78,11 @@ Attributes on items:
let x1 = ... [@@id1] [@@id2] and x2 = ... [@@id3] [@@id4]
The [@@id s] form, when used at the beginning of a signature or
structure, or after a double semi-colon (;;), defines an attribute
which stands as a stand-alone signature or structure item (not
attached to another item).
Floating attributes:
The [@@@id s] form defines an attribute which stands as a
stand-alone signature or structure item (not attached to another
item).
Example:
@ -89,13 +90,13 @@ Attributes on items:
[@@id1]
type t
[@@id2]
;; [@@id3] [@@id4]
;; [@@id5]
[@@@id3] [@@@id4]
[@@@id5]
type s
[@@id6]
end
Here, id1, id3, id4, id5 are stand-alone attributes, while
Here, id1, id3, id4, id5 are floating attributes, while
id2 is attached to the type t and id6 is attached to the type s.
=== Extension nodes
@ -249,9 +250,21 @@ to represent attributes.
It is now possible to start a signature or a structure with a ";;" token and to have two successive ";;" tokens.
Rationale:
It makes it possible to always prefix a "standalone" attribute by ";;" independently
from its context (this will work at the beginning of the signature/structure and after
another item finished with ";;").
In an intermediate version of this branch, floating attributes shared
the same syntax as item attributes, with the constraints that they
had to appear either at the beginning of their structure or signature,
or after ";;". The relaxation above made is possible to always prefix
a floating attributes by ";;" independently of its context.
Floating attributes now have a custom syntax [@@@id], but this changes
is harmless, and the same argument holds for toplevel expressions:
it is always possile to write:
;; print_endline "bla";;
without having to care about whether the previous structure item
ends with ";;" or not.
-- Relaxing the syntax for exception declarations

View File

@ -446,6 +446,7 @@ rule token = parse
| "[%" { LBRACKETPERCENT }
| "[%%" { LBRACKETPERCENTPERCENT }
| "[@@" { LBRACKETATAT }
| "[@@@" { LBRACKETATATAT }
| "!" { BANG }
| "!=" { INFIXOP0 "!=" }
| "+" { PLUS }

View File

@ -354,6 +354,7 @@ let mkexp_attrs d attrs =
%token LPAREN
%token LBRACKETAT
%token LBRACKETATAT
%token LBRACKETATATAT
%token MATCH
%token METHOD
%token MINUS
@ -500,8 +501,7 @@ toplevel_phrase:
| EOF { raise End_of_file }
;
top_structure:
str_attribute top_structure { $1 :: $2 }
| seq_expr post_item_attributes { [mkstrexp $1 $2] }
seq_expr post_item_attributes { [mkstrexp $1 $2] }
| top_structure_tail { $1 }
;
top_structure_tail:
@ -603,8 +603,7 @@ module_expr:
;
structure:
str_attribute structure { $1 :: $2 }
| seq_expr post_item_attributes structure_tail { mkstrexp $1 $2 :: $3 }
seq_expr post_item_attributes structure_tail { mkstrexp $1 $2 :: $3 }
| structure_tail { $1 }
;
structure_tail:
@ -612,9 +611,6 @@ structure_tail:
| SEMISEMI structure { $2 }
| structure_item structure_tail { $1 :: $2 }
;
str_attribute:
post_item_attribute { mkstr(Pstr_attribute $1) }
;
structure_item:
LET ext_attributes rec_flag let_bindings
{
@ -661,6 +657,8 @@ structure_item:
{ mkstr(Pstr_include ($2, $3)) }
| item_extension post_item_attributes
{ mkstr(Pstr_extension ($1, $2)) }
| floating_attribute
{ mkstr(Pstr_attribute $1) }
;
module_binding_body:
EQUAL module_expr
@ -708,16 +706,9 @@ module_type:
{ Mty.attr $1 $2 }
;
signature:
sig_attribute signature { $1 :: $2 }
| signature_tail { $1 }
;
signature_tail:
/* empty */ { [] }
| SEMISEMI signature { $2 }
| signature_item signature_tail { $1 :: $2 }
;
sig_attribute:
post_item_attribute { mksig(Psig_attribute $1) }
| signature_item signature { $1 :: $2 }
;
signature_item:
VAL val_ident COLON core_type post_item_attributes
@ -760,6 +751,8 @@ signature_item:
{ mksig(Psig_class_type (List.rev $3)) }
| item_extension post_item_attributes
{ mksig(Psig_extension ($1, $2)) }
| floating_attribute
{ mksig(Psig_attribute $1) }
;
module_declaration:
@ -2069,6 +2062,9 @@ attribute:
post_item_attribute:
LBRACKETATAT attr_id payload RBRACKET { ($2, $3) }
;
floating_attribute:
LBRACKETATATAT attr_id payload RBRACKET { ($2, $3) }
;
post_item_attributes:
/* empty */ { [] }
| post_item_attribute post_item_attributes { $1 :: $2 }