]> gerrit.simantics Code Review - simantics/platform.git/blob - bundles/org.simantics.scl.compiler/src/org/simantics/scl/compiler/internal/parsing/parser/SCL.grammar
New SCL syntax <<effects>>
[simantics/platform.git] / bundles / org.simantics.scl.compiler / src / org / simantics / scl / compiler / internal / parsing / parser / SCL.grammar
1
2 /******************************************************************************
3  * Initial
4  */
5
6 initial module ;
7 initial commands ;
8 initial import ;
9 initial type ;
10 initial exp ;
11 initial equationBlock ;
12
13 module
14     = (declaration (SEMICOLON declaration)*)?                # Module
15     ;
16
17 commands 
18     = command?                                               # OneCommand
19     | commands SEMICOLON command                             # ManyCommands 
20     ;
21     
22 command
23     = statement                                              # StatementCommand
24     | import                                                 # ImportCommand
25     ;
26
27 /******************************************************************************
28  * Declarations
29  */
30  
31 declarations
32     = LBRACE (declaration (SEMICOLON declaration)*)? RBRACE  # Declarations
33     ;
34
35 declaration
36     = MODULE LBRACE (field (COMMA field)*)? RBRACE           # ModuleHeader
37     | var (COMMA var)* HASTYPE type                          # TypeAnnotation
38     | bexp rhs                                               # ValueDefinition
39     | DATA ID+ (EQUALS constructor (BAR constructor)*)?      # DataDefinition
40     | TYPE ID+ EQUALS type                                   # TypeDefinition
41     | CLASS context? ID+ 
42       (BAR fundeps)?
43       (WHERE declarations)?                                  # ClassDefinition
44     | INSTANCE context? ID atype+ (WHERE declarations)?      # InstanceDefinition
45     | DERIVING INSTANCE context? ID atype+                   # DerivingInstanceDefinition
46     | BEGIN_STRING END_STRING                                # DocumentationString
47     | ANNOTATION_ID aexp*                                    # Annotation
48     | (INFIX | INFIXL | INFIXR) INTEGER var (COMMA var)*     # PrecedenceDefinition
49     | import                                                 # JustImport
50     | IMPORTJAVA BEGIN_STRING END_STRING WHERE declarations  # ImportJava
51     | EFFECT ID BEGIN_STRING END_STRING 
52                 BEGIN_STRING END_STRING                      # EffectDefinition
53     | (RULE | ABSTRACT_RULE) ID 
54       (EXTENDS ID (COMMA ID)*)?
55       WHERE ruleDeclarations                                 # RuleDefinition
56     | MAPPING_RELATION ID atype*                             # MappingRelationDefinition
57     | bexp FOLLOWS ruleDeclarations                          # RelationDefinition
58     | RULESET ID WHERE statements                            # RulesetDefinition
59     ;
60
61 import
62     = (IMPORT | INCLUDE)
63       BEGIN_STRING END_STRING
64       (AS ID)?    
65       importSpec?                                            # Import
66     ;
67     
68 importSpec 
69     = LPAREN (importItem (COMMA importItem)*)? RPAREN         # ImportShowing
70     | HIDING LPAREN (importItem (COMMA importItem)*)? RPAREN  # ImportHiding
71     ;
72
73 importItem 
74     = ID                                                      # ImportValueItem
75 //    | (TYPE | DATA) ID                                        # ImportTypeItem
76 //    | CLASS ID                                                # ImportClassItem
77     ;
78     
79
80 constructor
81     = (ANNOTATION_ID aexp)* ID atype*                        # Constructor
82     | (ANNOTATION_ID aexp)* ID LBRACE
83           fieldDeclaration (COMMA fieldDeclaration)* RBRACE  # RecordConstructor
84     ;
85     
86 fieldDeclaration
87     = ID HASTYPE type                                        # FieldDescription
88     ;
89
90 rhs = EQUALS exp (WHERE statements)?                         # SimpleRhs
91     | guardedExpEq+ (WHERE statements)?                      # GuardedRhs
92     ;
93
94 guardedExpEq
95     = BAR exp (COMMA exp)* EQUALS exp                        # GuardedExpEq
96     ;
97     
98 fundep
99     = ID+ ARROW ID                                           # Fundep
100     ;
101
102 fundeps
103     = fundep (COMMA fundep)*                                 # Fundeps
104     ;
105
106 /******************************************************************************
107  * Rules
108  */
109
110 ruleDeclarations
111     = LBRACE (ruleDeclaration (SEMICOLON ruleDeclaration)*)? RBRACE  # RuleDeclarations
112     ;
113
114 ruleDeclaration
115     = query                                                  # QueryRuleDeclaration
116     | ANNOTATION_ID aexp*                                    # Annotation
117     ;
118     
119 /******************************************************************************
120  * Expressions
121  */
122  
123 exp = bexp (HASTYPE type)?                                   # LocalTypeAnnotation, shift HASTYPE, shift COLON
124     ;
125
126 bexp 
127     =  MINUS? lexp (symbol lexp)*                            # Binary, shift MINUS, shift SYMBOL,
128                                                                shift LESS, shift GREATER, shift SEPARATED_DOT,
129                                                                shift ESCAPED_ID
130     ;
131
132 lexp 
133     = faexp+                                                 # Apply, shift ID, shift LAMBDA, shift LAMBDA_MATCH,
134                                                                shift LET, shift INTEGER, shift BEGIN_STRING,
135                                                                shift IF, shift MATCH, shift DO,
136                                                                shift MDO, shift EDO, shift ENFORCE, shift BLANK,
137                                                                shift FLOAT, shift LPAREN, shift LBRACKET,
138                                                                shift ESCAPED_SYMBOL, shift CHAR, shift LBRACE,
139                                                                shift WHEN, shift ATTACHED_HASH,
140                                                                shift SELECT, shift SELECT_FIRST, shift SELECT_DISTINCT,
141                                                                shift TRANSFORMATION, shift EQ, shift CHR_SELECT
142     ; 
143
144 faexp
145     = aexp ((ATTACHED_DOT | ATTACHED_HASH) accessor)*        # FieldAccess, shift ATTACHED_DOT, shift ATTACHED_HASH
146     ;
147
148 accessor
149     = ID                                                     # IdAccessor
150     | BEGIN_STRING END_STRING                                # StringAccessor
151     | LPAREN exp RPAREN                                      # ExpAccessor
152     ;
153
154 aexp 
155     = LAMBDA aexp+ ARROW exp                                 # Lambda, shift HASTYPE
156     | LAMBDA_MATCH LBRACE case (SEMICOLON case)* RBRACE      # LambdaMatch, shift HASTYPE
157     | LET statements IN exp                                  # Let, shift HASTYPE
158     | IF exp THEN exp (ELSE exp)?                            # If, shift HASTYPE, shift ELSE
159     | MATCH exp WITH
160       LBRACE case (SEMICOLON case)* RBRACE                   # Match
161     | (DO | MDO | EDO) statements                            # Do
162     | (SELECT | SELECT_FIRST | SELECT_DISTINCT) 
163       exp WHERE queryBlock                                   # Select
164     | CHR_SELECT 
165       exp WHERE verboseChrQuery                              # CHRSelect
166     | ENFORCE queryBlock                                     # Enforce
167     //| WHEN queryBlock SEMICOLON exp                          # When
168     | var                                                    # Var
169     | ATTACHED_HASH ID                                       # HashedId
170     | BLANK                                                  # Blank
171     | INTEGER                                                # Integer
172     | FLOAT                                                  # Float
173     | stringLiteral                                          # String
174     | CHAR                                                   # Char
175     | LPAREN (exp (COMMA exp)*)? RPAREN                      # Tuple
176     | LPAREN exp ARROW exp RPAREN                            # ViewPattern    
177     | LPAREN symbolWithoutMinus lexp RPAREN                  # RightSection
178     | LPAREN lexp symbol RPAREN                              # LeftSection
179     | LBRACKET (exp (COMMA exp)*)? RBRACKET                  # ListLiteral
180     | LBRACKET exp DOTDOT exp RBRACKET                       # Range
181     | LBRACKET exp BAR 
182       listQualifier (COMMA listQualifier)* RBRACKET          # ListComprehension
183     | ID AT aexp                                             # As
184     | ID LBRACE (field (COMMA field)*)? RBRACE               # Record
185     | TRANSFORMATION ID WHERE queryBlock                     # Transformation
186     | EQ LBRACE equationBlock RBRACE                         # Eq
187     ;
188     
189 stringLiteral
190     = BEGIN_STRING (SUSPEND_STRING exp CONTINUE_STRING)* 
191       END_STRING                                             # StringLiteral
192     ;
193
194 statements
195     = LBRACE (statement (SEMICOLON statement)*)? RBRACE      # Statements
196     ;
197
198 statement
199     = exp                                                    # GuardStatement
200     | exp rhs                                                # LetStatement
201     | exp BINDS exp                                          # BindStatement
202     | exp FOLLOWS queryBlock                                 # RuleStatement
203     | chrQuery IMPLIES chrQuery                              # CHRStatement
204     | WHEN verboseChrQuery THEN_AFTER_WHEN verboseChrQuery   # VerboseCHRStatement
205     | CONSTRAINT constructor                                 # ConstraintStatement
206     | INCLUDE ID aexp                                        # LocalInclude
207     ;
208
209 verboseChrQuery
210     = LBRACE chrQuery (SEMICOLON chrQuery)* RBRACE           # VerboseCHRConjunction
211     ;
212     
213
214 chrQuery 
215     = chrQueryPart (COMMA chrQueryPart)*                     # CHRConjunction
216     ;
217
218 chrQueryPart
219     = exp                                                    # CHRAtom
220     | exp EQUALS exp                                         # CHREquals
221     | exp BINDS exp                                          # CHRBinds
222     ;
223
224 listQualifier
225     = exp                                                    # GuardQualifier
226     | exp EQUALS exp                                         # LetQualifier
227     | exp BINDS exp                                          # BindQualifier
228     | THEN exp (BY exp)?                                     # ThenQualifier
229     ;
230     
231 case
232     = exp caseRhs                                            # Case
233     ;
234
235 caseRhs 
236     = ARROW exp (WHERE statements)?                          # SimpleCaseRhs
237     | guardedExpArrow+ (WHERE statements)?                   # GuardedCaseRhs
238     ;
239
240 guardedExpArrow
241     = BAR exp (COMMA exp)* ARROW exp                         # GuardedExpArrow
242     ;
243
244 field
245     = ID EQUALS exp                                          # Field
246     | ID                                                     # FieldShorthand
247     | DOTDOT                                                 # Wildcard
248     ;
249
250 /******************************************************************************
251  * Queries
252  */
253
254 queryBlock 
255     = LBRACE (query (SEMICOLON query)*)? RBRACE              # QueryBlock
256     ;
257
258 query
259     = exp                                                    # GuardQuery, shift BINDS, shift EQUALS
260     | exp EQUALS exp                                         # EqualsQuery
261     | exp BINDS exp                                          # BindQuery
262     | QUERY_OP queryBlock                                    # CompositeQuery
263     ;
264
265 /******************************************************************************
266  * Equations
267  */
268  
269 equationBlock
270     = (equation (SEMICOLON equation)*)?                      # EquationBlock
271     ;
272     
273 equation
274     = exp                                                    # GuardEquation
275     | exp EQUALS exp                                         # BasicEquation
276     ;
277  
278 /******************************************************************************
279  * Types
280  */
281
282 context
283     = LPAREN type (COMMA type)* RPAREN IMPLIES               # Context
284     ;
285
286 type 
287     = etype ((ARROW | IMPLIES) etype)*                       # Arrow, shift ARROW, shift IMPLIES
288     ;
289
290 etype
291     = LESS ID (COMMA ID)* GREATER btype                      # Effect
292     | btype                                                  # JustEtype
293     | FORALL ID+ (SEPARATED_DOT | ATTACHED_DOT) type         # ForAll
294     ;
295
296 btype 
297     = atype+                                                 # ApplyType, shift ID, shift LPAREN,
298                                                                shift LBRACKET
299     ;
300
301 atype
302     = ID                                                     # TypeVar
303     | DOUBLE_LESS ID (COMMA ID)* DOUBLE_GREATER              # PlainEffect
304     | LPAREN (type (COMMA type)*)? RPAREN                    # TupleType
305     | LBRACKET type RBRACKET                                 # ListType
306     | LBRACKET RBRACKET                                      # ListTypeConstructor
307     | LPAREN COMMA+ RPAREN                                   # TupleTypeConstructor
308     ;
309
310 /******************************************************************************
311  * Variables and symbols
312  */
313
314 var = ID                                                     # VarId
315     | ESCAPED_SYMBOL                                         # EscapedSymbol
316     | LPAREN COMMA+ RPAREN                                   # TupleConstructor
317     ;
318
319 symbol
320     = SYMBOL                                                 # Symbol
321     | ESCAPED_ID                                             # EscapedId
322     | MINUS                                                  # Minus
323     | LESS                                                   # Less
324     | GREATER                                                # Greater
325     | DOUBLE_LESS                                            # DoubleLess
326     | DOUBLE_GREATER                                         # DoubleGreater
327     | SEPARATED_DOT                                          # Dot
328     ;
329     
330 symbolWithoutMinus
331     = SYMBOL                                                 # Symbol
332     | ESCAPED_ID                                             # EscapedId
333     | LESS                                                   # Less
334     | GREATER                                                # Greater
335     | SEPARATED_DOT                                          # Dot
336     ;
337
338 /******************************************************************************
339  * Auxiliary tokens
340  */
341 dummy = COMMENT EOL                                          # Dummy 
342       ;