source: branches/xtext-MDT/org.modelica.xtext.core/src/org/modelica/xtext/ModelicaAST.xtext @ 553

Last change on this file since 553 was 553, checked in by nasko, 15 years ago

Fixed some problem with the grammar file

File size: 26.7 KB
Line 
1grammar org.modelica.xtext.ModelicaAST hidden(WS, ML_COMMENT, SL_COMMENT)
2
3import "http://www.eclipse.org/emf/2002/Ecore" as ecore
4import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Program" as Program
5import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Within" as Within
6import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Class" as Class
7import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ClassDef" as ClassDef
8import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//EnumDef" as EnumDef
9import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//EnumLiteral" as EnumLiteral
10import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ClassPart" as ClassPart
11import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ElementItem" as ElementItem
12import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Element" as Element
13import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ConstrainClass" as ConstrainClass
14import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ElementSpec" as ElementSpec
15import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//InnerOuter" as InnerOuter
16import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Import" as Import
17import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ComponentItem" as ComponentItem
18import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ComponentCondition" as ComponentCondition
19import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Component" as Component
20import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//EquationItem" as EquationItem
21import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//AlgorithmItem" as AlgorithmItem
22import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Equation" as Equation
23import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//AlgorithmStatement" as AlgorithmStatement
24import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Modifications" as Modifications
25import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ElementArg" as ElementArg
26import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//RedeclareKeywords" as RedeclareKeywords
27import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Each" as Each
28import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ElementAttributes" as ElementAttributes
29import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Variability" as Variability
30import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Direction" as Direction
31import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ArrayDim" as ArrayDim
32import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Exp" as Exp
33import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//FunctionArgs" as FunctionArgs
34import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//NamedArg" as NamedArg
35import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Operator" as Operator
36import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Subscript" as Subscript
37import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ComponentRef" as ComponentRef
38import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Path" as Path
39import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Restriction" as Restriction
40import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Annotation" as Annotation
41import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Comment" as Comment
42import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//ExternalDecl" as ExternalDecl
43import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//TimeStamp" as TimeStamp
44import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//Iterators" as Iterators
45import "platform:/resource/org.modelica.emf/model/OpenModelicaAbstactSyntax.ecore#//TypeSpec" as TypeSpec
46
47/*
48 * Copyright (c) 2009 - currentYear,
49    Adrian Pop [adrpo@ida.liu.se],
50    Atanas Pavlov [nasko.js@gmail.com]
51 * All rights reserved.
52 */
53
54 
55
56
57/*------------------------------------------------------------------
58 * PARSER RULES
59 *------------------------------------------------------------------*/
60
61StorageUnit returns Program::PROGRAM :
62    withinClause=WithinClause
63    (classes+=Class ';')*
64    ;
65
66WithinClause returns Within::uWithin :
67    {Within::WITHIN} 'within' (path=Path)? ';'
68    | {Within::TOP}
69    ;
70
71Class returns Class::uClass :
72    {Class::CLASS}
73    finalPrefix?=('final')? encapsulatedPrefix?=('encapsulated')? partialPrefix?=('partial')?
74    restriction=Restriction (name=IDENT body=ClassDefinition | 'extends' body=ClassDefinitionExtends)
75    ;
76
77InnerClass returns Class::uClass :
78    {Class::CLASS}
79    encapsulatedPrefix?=('encapsulated')? partialPrefix?=('partial')?
80    restriction=Restriction (name=IDENT body=ClassDefinition | 'extends' body=ClassDefinitionExtends)
81    ;
82
83ClassDefinition returns ClassDef::uClassDef :
84    ClassDefinitionDerived
85    | ClassDefinitionEnum
86    | ClassDefinitionOverload
87    | ClassDefinitionPartialDer
88    | ClassDefinitionParts
89    ;
90   
91ClassDefinitionDerived returns ClassDef::DERIVED :
92    '=' attributes=ElementAttributes typeSpec=TypeSpecification
93    ('(' arguments+=ElementArg (',' arguments+=ElementArg)* ')')?  comment=Comment
94    ;
95
96ClassDefinitionEnum returns ClassDef::ENUMERATION :
97    '=' 'enumeration' '(' enumLiterals=EnumerationDefinition ')' comment=Comment
98    ;
99
100ClassDefinitionOverload returns ClassDef::OVERLOAD :
101    '=' 'overload' '(' functionNames+=Path (',' functionNames+=Path)* ')' comment=Comment
102    ;
103
104// CHECK Comment?
105ClassDefinitionPartialDer returns ClassDef::PDER :
106    '=' 'der' '(' functionName=Path (',' vars+=IDENT)+ ')'
107    ;
108// CHECK Comment or StringComment
109ClassDefinitionExtends returns ClassDef::CLASS_EXTENDS :
110    baseClassName=IDENT ('('
111    modifications+=ElementArg ( ',' modifications+=ElementArg)* ')')?
112    comment=StringComment? (parts+=ClassPartInitial)?
113    (parts+=ClassPart)* (parts+=ClassPartExternal)?
114    'end' nameEnd=IDENT
115    ;
116
117ClassDefinitionParts returns ClassDef::PARTS :
118    comment=StringComment? (classParts+=ClassPartInitial)?
119    (classParts+=ClassPart)* (classParts+=ClassPartExternal)?
120    'end' nameEnd=IDENT
121    ;
122EnumerationDefinition returns EnumDef::uEnumDef :
123    {EnumDef::ENUMLITERALS} enumLiterals+=EnumLiteral (',' enumLiterals+=EnumLiteral)*
124    | {EnumDef::ENUM_COLON} ':'
125    ;
126
127EnumLiteral returns EnumLiteral::uEnumLiteral :
128    {EnumLiteral::ENUMLITERAL} literal=IDENT comment=Comment
129    ;
130   
131ClassPart returns ClassPart::uClassPart :
132    {ClassPart::PUBLIC} 'public' (contents+=ElementItem)*
133    |{ClassPart::PROTECTED} 'protected' (contents+=ElementItem)*
134    |{ClassPart::EQUATIONS} 'equation' (contents+=EquationItem)*
135    |{ClassPart::INITIALEQUATIONS} 'initial' 'equation' (contents+=EquationItem)*
136    |{ClassPart::ALGORITHMS} 'algorithm' (contents+=AlgorithmItem)*
137    |{ClassPart::INITIALALGORITHMS} 'initial' 'algorithm' (contents+=AlgorithmItem)*
138    ;
139
140ClassPartInitial returns ClassPart::uClassPart :
141    {ClassPart::PUBLIC} (contents+=ElementItem)+
142    ;
143   
144ClassPartExternal returns ClassPart::uClassPart :
145    {ClassPart::EXTERNAL} 'external' externalDecl=ExternalDeclaration ';'
146    (annotationNode=Annotation ';')?
147    ;
148
149ElementItem returns ElementItem::uElementItem :
150    {ElementItem::ELEMENTITEM} element=Element ';'
151    |{ElementItem::ANNOTATIONITEM} annotation_=Annotation ';'
152    ;
153
154// FIXME Figure out the text thing
155// fix redeclareKeyword>s< ?=('redeclare')?
156//Element returns Element::uElement :
157//  ElementElement
158    //|{TEXT}
159    //|{DEFINEUNIT}
160    //;
161   
162// FIXME constrainedby clause   
163Element returns Element::ELEMENT:
164    innerOuter=InnerOuterUnspecified (specification=ElementSpecificationImport | specification=ElementSpecificationExtends)
165    | redeclareKeywords=RedeclareKeyword? finalPrefix?='final'?
166        innerOuter=InnerOuter (specification=ElementSpecificationClassDefinition | specification=ElementSpecificationComponents)
167    | (redeclareKeywords=RedeclareReplaceableKeyword | redeclareKeywords=ReplaceableKeyword) innerOuter=InnerOuter
168        (specification=ElementSpecificationClassDefinition | specification=ElementSpecificationComponents) 
169    constrainClass=ConstrainClass?
170    ;
171
172ConstrainClass returns ConstrainClass::uConstrainClass :
173    {ConstrainClass::CONSTRAINCLASS} elementSpec=ElementSpecificationConstrainedby comment=Comment?
174    ;
175
176/*
177ElementSpecification returns ElementSpec::uElementSpec :
178    ElementSpecificationImport
179    |ElementSpecificationExtends
180    |ElementSpecificationClassDefinition
181    |ElementSpecificationComponents
182    ;
183*/
184ElementSpecificationImport returns ElementSpec::uElementSpec :
185    {ElementSpec::IMPORT} 'import' import_=Import comment=Comment
186    ;
187
188ElementSpecificationExtends returns ElementSpec::uElementSpec :
189    {ElementSpec::EXTENDS} 'extends' path=Path ( '('
190    elementArg+=ElementArg (',' elementArg+=ElementArg)* ')' )? annotationOpt=Annotation?
191    ;
192
193ElementSpecificationConstrainedby returns ElementSpec::uElementSpec :
194    {ElementSpec::EXTENDS} 'constrainedby' path=Path ( '('
195    elementArg+=ElementArg (',' elementArg+=ElementArg)* ')' )? annotationOpt=Annotation?
196    ;
197
198/* FIXME 'replaceable' both here and in InnerClass */
199ElementSpecificationClassDefinition returns ElementSpec::uElementSpec :
200    {ElementSpec::CLASSDEF} /*replaceable_?=('replaceable')?*/ class_=InnerClass
201    ;
202   
203ElementSpecificationComponents returns ElementSpec::uElementSpec :
204    {ElementSpec::COMPONENTS} attributes=ElementAttributes typeSpec=TypeSpecification
205    components+=ComponentItem (',' components+=ComponentItem)*
206    ;
207       
208InnerOuter returns InnerOuter::uInnerOuter :
209    {InnerOuter::INNEROUTER} 'inner' 'outer'
210    |{InnerOuter::INNER} 'inner'
211    |{InnerOuter::OUTER} 'outer'
212    |InnerOuterUnspecified
213    ;
214
215InnerOuterUnspecified returns InnerOuter::uInnerOuter :
216    {InnerOuter::UNSPECIFIED}
217    ;
218
219// FIXME the unqualified import- perhaps in a M2M transformation
220Import returns Import::uImport :
221    {Import::NAMED_IMPORT} name=IDENT '=' path=Path
222    |{Import::QUAL_IMPORT} path=Path
223    //|{UNQUAL_IMPORT} path=Path
224    ;
225
226ComponentItem returns ComponentItem::uComponentItem :
227    {ComponentItem::COMPONENTITEM} component=Component condition=ComponentCondition? comment=Comment
228    ;
229
230ComponentCondition returns ComponentCondition::ComponentCondition :
231    'if' condition=Expression
232    ;
233
234Component returns Component::uComponent :
235    {Component::COMPONENT} name=IDENT arrayDim=ArrayDim modification=Modification?
236    ;
237
238EquationItem returns EquationItem::uEquationItem :
239    {EquationItem::EQUATIONITEM} equation_=Equation comment=Comment ';'
240    | {EquationItem::EQUATIONITEMANN} annotation_=Annotation ';'
241    ;
242
243AlgorithmItem returns AlgorithmItem::uAlgorithmItem :
244    {AlgorithmItem::ALGORITHMITEM} algorithm_=AlgorithmStatement comment=Comment ';'
245    | {AlgorithmItem::ALGORITHMITEMANN} annotation_=Annotation ';'
246    ;
247
248Equation returns Equation::uEquation :
249    EquationIf | EquationEquals | EquationConnect | EquationFor | EquationWhenEq
250    | EquationNoRetCall
251    //|EqFailure
252    ;
253   
254EquationIf returns Equation::EQ_IF :
255    'if' ifExp=Expression 'then' (equationTrueItems+=EquationItem)*
256    (elseIfBranches+=ElseIfBranch)*
257    ('else' (equationElseItems+=EquationItem)*)?
258    'end' 'if'
259    ;
260
261ElseIfBranch returns Equation::tuple_ElseIfBranch :
262    'elseif' exp=Expression 'then' (equationItem+=EquationItem)*
263    ;
264   
265EquationEquals returns Equation::EQ_EQUALS :
266    leftSide=ExprRange '=' rightSide=Expression
267    ;
268EquationNoRetCall returns Equation::EQ_NORETCALL :
269    functionName=ComponentRef '(' functionArgs=FunctionArguments? ')'
270    ;
271
272EquationConnect returns Equation::EQ_CONNECT :
273    'connect' '(' connector1=ComponentRef ',' connector2=ComponentRef ')'
274    ;
275
276EquationFor returns Equation::EQ_FOR :
277    'for' iterators=ForIterators 'loop' (forEquations+=EquationItem)* 'end' 'for'
278    ;
279
280EquationWhenEq returns Equation::EQ_WHEN_E :
281    'when' whenExp=Expression 'then' (whenEquations+=EquationItem)*
282    (elseWhenEquations+=ElseWhenEquationBranch)*
283    'end' 'when'
284    ;
285
286ElseWhenEquationBranch returns Equation::tuple_ElseWhenEquation :
287    'elsewhen' exp=Expression 'then' (equationItem+=EquationItem)*
288    ;   
289
290AlgorithmStatement returns AlgorithmStatement::uAlgorithmStatement :
291    AlgorithmIf | AlgorithmAssign | AlgorithmFor | AlgorithmWhen
292    |AlgorithmNoRetCall
293    | AlgorithmReturn | AlgorithmWhile | AlgorithmBreak
294    ;
295
296AlgorithmIf returns AlgorithmStatement::uAlgorithmStatement :
297    {AlgorithmStatement::ALG_IF}
298    'if' ifExp=Expression 'then' (trueBranch+=AlgorithmItem)*
299    (elseIfAlgorithmBranch+=ElseIfAlgorithmBranch)*
300    ('else' (elseBranch+=AlgorithmItem)*)?
301    'end' 'if'
302    ;
303
304ElseIfAlgorithmBranch returns AlgorithmStatement::tuple_ElseIfAlgorithmBranch :
305    'elseif' exp=Expression 'then' (algorithmItem+=AlgorithmItem)*
306    ;
307
308AlgorithmAssign returns AlgorithmStatement::uAlgorithmStatement :
309    {AlgorithmStatement::ALG_ASSIGN} assignComponent=ExprRange ':=' value=Expression
310    ;
311AlgorithmNoRetCall returns  AlgorithmStatement::uAlgorithmStatement:
312    {AlgorithmStatement::ALG_NORETCALL}
313    functionCall=ComponentRef '(' functionArgs=FunctionArguments? ')'
314    ;
315
316AlgorithmFor returns AlgorithmStatement::uAlgorithmStatement :
317    {AlgorithmStatement::ALG_FOR} 'for' iterators=ForIterators 'loop' (forBody+=AlgorithmItem)* 'end' 'for'
318    ;
319
320AlgorithmWhen returns AlgorithmStatement::uAlgorithmStatement :
321    {AlgorithmStatement::ALG_WHEN_A}
322    'when' boolExpr=Expression 'then' (whenBody+=AlgorithmItem)
323    (elseWhenAlgorithmBranch+=ElseWhenAlgorithmBranch)*
324    'end' 'when'
325    ;
326
327ElseWhenAlgorithmBranch returns AlgorithmStatement::tuple_ElseWhenAlgorithmBranch :
328    'elsewhen' exp=Expression 'then' (algorithmItem+=AlgorithmItem)*
329    ;   
330
331AlgorithmReturn returns AlgorithmStatement::ALG_RETURN :
332    {AlgorithmStatement::ALG_RETURN} 'return'
333    ;
334
335AlgorithmWhile returns AlgorithmStatement::ALG_WHILE :
336    {AlgorithmStatement::ALG_WHILE} 'while' boolExpr=Expression 'loop' (whileBody+=AlgorithmItem)* 'end' 'while'
337    ;
338
339AlgorithmBreak returns AlgorithmStatement::ALG_BREAK :
340    {AlgorithmStatement::ALG_BREAK} 'break'
341    ;
342
343Modification returns Modifications::uModification :
344    {Modifications::CLASSMOD}   (
345    '(' elementArgList+=ElementArg (',' elementArgList+=ElementArg)* ')' ('=' expOption=Expression)?
346    | ('='|':=') expOption=Expression)
347    ;
348   
349ElementArg returns ElementArg::uElementArg :
350    {ElementArg::MODIFICATION} each_=Each finalItem?=('final')?
351    componentRef=ComponentRef modification=Modification?
352    comment=StringComment?
353    |{ElementArg::REDECLARATION} each_=Each finalItem?=('final')?
354    redeclareKeywords=( ReplaceableKeyword | RedeclareReplaceableKeyword )
355    elementSpec=( ElementSpecificationClassDefinition | ElementSpecificationComponents1 )
356    constrainClass=ConstrainClass?
357    |{ElementArg::REDECLARATION} each_=Each finalItem?=('final') redeclareKeywords=RedeclareKeyword
358    elementSpec=( ElementSpecificationClassDefinition | ElementSpecificationComponents1 )
359    ;
360
361ElementSpecificationComponents1 returns ElementSpec::uElementSpec :
362    {ElementSpec::COMPONENTS} attributes=ElementAttributes typeSpec=TypeSpecification
363    components+=ComponentItem ';'
364    ;
365   
366ReplaceableKeyword returns RedeclareKeywords::uRedeclareKeywords :
367    {RedeclareKeywords::REPLACEABLE} 'replaceable'
368    ;
369
370RedeclareKeyword returns RedeclareKeywords::uRedeclareKeywords :
371    {RedeclareKeywords::REDECLARE} 'redeclare'
372    ;
373
374RedeclareReplaceableKeyword returns RedeclareKeywords::uRedeclareKeywords :
375    {RedeclareKeywords::REDECLARE_REPLACEABLE} 'redeclare' 'replaceable'
376    ;
377
378
379Each returns Each::uEach :
380    {Each::EACH} 'each'
381    |{Each::NON_EACH}
382    ;
383
384ElementAttributes returns ElementAttributes::uElementAttributes  :
385    {ElementAttributes::ATTR} (flowPrefix?='flow'|streamPrefix?='stream')?
386    variability=Variability direction=Direction arrayDim=ArrayDim?
387    ;
388
389Variability returns Variability::uVariability :
390    {Variability::CONST} 'constant'
391    |{Variability::PARAM} 'parameter'
392    |{Variability::DISCRETE} 'discrete'
393    |{Variability::VAR}
394    ;
395   
396Direction returns Direction::uDirection :
397    {Direction::INPUT} 'input'
398    |{Direction::OUTPUT} 'output'
399    |{Direction::BIDIR}
400    ;   
401   
402ArrayDim returns ArrayDim::ArrayDim :
403    {ArrayDim::ArrayDim} ('[' subscripts+=Subscript (',' subscripts+=Subscript)* ']')?
404    ;   
405
406Expression returns Exp::uExp :
407    ExprIf | ExprRange
408    ;
409   
410ExprIf returns Exp::uExp :
411    {Exp::IFEXP} 'if' ifExp=Expression 'then' trueBranch=Expression
412    (elseIfBranch+=ExprElseIfBranchTuple)*
413    ('else' elseBranch=Expression)
414    ;
415
416ExprElseIfBranchTuple returns Exp::tuple_ElseIfBranch :
417    'elseif' exp1=Expression 'then' exp2=Expression
418    ;
419
420ExprRange returns Exp::uExp :
421    ExprLogical ({Exp::RANGE.start=current} ':'  (step=ExprLogical ':' stop=ExprLogical | stop=ExprLogical) )?
422    ;
423   
424ExprLogical returns Exp::uExp :
425    ExprLogicalTerm ({Exp::LBINARY.exp1=current} op=OperatorOr exp2=ExprLogical)?
426    ;
427   
428ExprLogicalTerm returns Exp::uExp :
429    ExprLogicalFactor ({Exp::LBINARY.exp1=current}  op=OperatorAnd exp2=ExprLogicalTerm)?
430    ;
431   
432ExprLogicalFactor returns Exp::uExp :
433    ExprRelation |
434    {Exp::LUNARY} op=OperatorNot exp=ExprRelation
435    ;
436
437ExprRelation returns Exp::uExp :
438    ExprArithmetic
439    ({Exp::RELATION.exp1=current} op = (OperatorLess | OperatorLessEq | OperatorGreater |
440    OperatorGreaterEq | OperatorEqual | OperatorEqual)  exp2=ExprArithmetic)?
441    ;
442
443ExprArithmetic returns Exp::uExp :
444    ExprUnaryArithmetic
445    ({Exp::BINARY.exp1=current} op=(OperatorAdd | OperatorSub | OperatorAddEW | OperatorSubEW)
446    exp2=ExprArithmetic2)?
447    ;
448
449ExprArithmetic2 returns Exp::uExp :
450    ExprArithmeticTerm
451    ({Exp::BINARY.exp1=current} op=(OperatorAdd | OperatorSub | OperatorAddEW | OperatorSubEW)
452    exp2=ExprArithmetic2)?
453    ;
454
455ExprUnaryArithmetic returns Exp::uExp :
456    ExprArithmeticTerm |
457    {Exp::UNARY} op=(OperatorUnPlus | OperatorUnMinus | OperatorUnPlusEW | OperatorUnMinusEW)
458    exp=ExprArithmeticTerm
459    ;
460
461ExprArithmeticTerm returns Exp::uExp :
462    ExprArithmeticFactor 
463    ( {Exp::BINARY.exp1=current} op=(OperatorMul | OperatorDiv | OperatorMulEW | OperatorDivEW)
464    exp2=ExprArithmeticTerm)?
465    ;
466
467ExprArithmeticFactor returns Exp::uExp :
468    ExprPrimary ({Exp::BINARY.exp1=current} op=(OperatorPow | OperatorPowEW) exp2=ExprPrimary)?
469    ;
470
471ExprPrimary returns Exp::uExp :
472    ExprInt | ExprReal | ExprComponentRefOrCall | ExprString | ExprBool | ExprArray
473    | ExprMatrix
474    | ExprTuple | ExprEnd | ExprDer
475    ;
476   
477ExprInt returns Exp::INTEGER :
478    value=UNSIGNED_INTEGER
479    ;
480
481ExprReal returns Exp::REAL :
482    value=UNSIGNED_REAL
483    ;
484
485ExprComponentRefOrCall returns Exp::uExp :
486    {Exp::CALL_INITIAL} 'initial' '(' ')'
487    | ExprFunctionCall
488    | ExprComponentRef
489    ;
490
491ExprComponentRef returns Exp::uExp :
492    {Exp::CREF} componentRef=ComponentRef
493    ;
494
495ExprFunctionCall returns Exp::uExp :
496    {Exp::CALL} function=ComponentRef '(' functionArgs=FunctionArguments? ')'
497    ;
498   
499ExprString returns Exp::STRING :
500    value=STRING
501    ;
502     
503ExprBool returns Exp::BOOL :
504    value=BOOL_VAL
505    ;
506       
507ExprArray returns Exp::ARRAY :
508    '{' arrayExp+=Expression (',' arrayExp+=Expression)* '}'
509    ;
510
511ExprMatrix returns Exp::MATRIX :
512    '[' matrix+=MatrixRow (';' matrix+=MatrixRow)* ']'
513    ;
514   
515MatrixRow returns Exp::tuple_Matrix :
516    exp+=Expression (',' exp+=Expression)*
517    ;
518   
519ExprTuple returns Exp::TUPLE :
520    {Exp::TUPLE} '(' expressions+=Expression (',' expressions+=Expression)* ')'
521    ;
522   
523ExprEnd returns Exp::END :
524    {Exp::END} 'end'
525    ;
526   
527ExprDer returns Exp::PARTEVALFUNCTION :
528    'der' '(' function_=ComponentRef (',' functionArgs=FunctionArguments)? ')'
529    ;
530   
531
532FunctionArguments returns FunctionArgs::uFunctionArguments :
533    FunctionArgumentsNormal
534    |FunctionArgumentsForIter
535    ;
536   
537FunctionArgumentsNormal returns FunctionArgs::uFunctionArguments :
538    {FunctionArgs::FUNCTIONARGS} args+=Expression (',' args+=Expression)* (',' argNames+=NamedArguments)*
539    |{FunctionArgs::FUNCTIONARGS} argNames+=NamedArguments (',' argNames+=NamedArguments)*
540    ;
541FunctionArgumentsForIter returns FunctionArgs::uFunctionArguments :
542    {FunctionArgs::FOR_ITER_FARG} exp=Expression 'for' iterators=ForIterator
543    ;
544/*
545FunctionNamedArguments returns FunctionArgs::uFunctionArguments :
546    {FunctionArgs::FUNCTIONARGS} argNames+=NamedArguments (',' argNames+=NamedArguments)*
547    ;
548*/
549       
550NamedArguments returns NamedArg::uNamedArg :
551    {NamedArg::NAMEDARG} argName=IDENT '=' argValue=Expression
552    ;
553
554/*
555    Operators
556*/
557/*
558OperatorLogical returns Operator::uOperator:
559    {Operator::LESS} '<' | {Operator::LESSEQ} '<=' | {Operator::GREATER} '>'
560    | {Operator::GREATEREQ} '>=' | {Operator::EQUAL} '==' | {Operator::NEQUAL} ('><'|'!=')
561    ;
562
563OperatorAddSub returns Operator::uOperator:
564    {Operator::SUB} '-' | {Operator::ADD} '+' | {Operator::ADD_EW} '.+' | {Operator::SUB_EW} '.-'
565    ;
566*/
567   
568OperatorAdd returns Operator::ADD :
569    {Operator::ADD} '+'
570    ;
571   
572OperatorSub returns Operator::SUB :
573    {Operator::SUB} '-'
574    ;
575   
576OperatorMul returns Operator::MUL :
577    {Operator::MUL} '*'
578    ;
579   
580OperatorDiv returns Operator::DIV :
581    {Operator::DIV} '/'
582    ;
583   
584OperatorPow returns Operator::POW :
585    {Operator::POW} '^'
586    ;
587
588OperatorUnPlus returns Operator::UPLUS :
589    {Operator::UPLUS} '+'
590    ;
591
592OperatorUnMinus returns Operator::UMINUS :
593    {Operator::UMINUS} '-'
594    ;
595
596OperatorAddEW returns Operator::ADD_EW :
597    {Operator::ADD_EW} '.+'
598    ;
599   
600OperatorSubEW returns Operator::SUB_EW :
601    {Operator::SUB_EW} '.-'
602    ;
603   
604OperatorMulEW returns Operator::MUL_EW :
605    {Operator::MUL_EW} '.*'
606    ;
607   
608OperatorDivEW returns Operator::DIV_EW :
609    {Operator::DIV_EW} './'
610    ;
611   
612OperatorPowEW returns Operator::POW_EW :
613    {Operator::POW_EW} '.^'
614    ;
615
616OperatorUnPlusEW returns Operator::UPLUS_EW :
617    {Operator::UPLUS_EW} '.+'
618    ;
619
620OperatorUnMinusEW returns Operator::UMINUS_EW :
621    {Operator::UMINUS_EW} '.-'
622    ;
623
624OperatorAnd returns Operator::AND :
625    {Operator::AND} 'and'
626    ;
627
628OperatorOr returns Operator::OR :
629    {Operator::OR} 'or'
630    ;
631   
632OperatorNot returns Operator::NOT :
633    {Operator::NOT} 'not'
634    ;
635   
636OperatorLess returns Operator::LESS :
637    {Operator::LESS} '<'
638    ;
639
640OperatorLessEq returns Operator::LESSEQ :
641    {Operator::LESSEQ} '<='
642    ;
643OperatorGreater returns Operator::GREATER :
644    {Operator::GREATER} '>'
645    ;
646   
647OperatorGreaterEq returns Operator::GREATEREQ :
648    {Operator::GREATEREQ} '>='
649    ;
650OperatorEqual returns Operator::EQUAL :
651    {Operator::EQUAL} '=='
652    ;
653   
654OperatorNotEqual returns Operator::NEQUAL :
655    {Operator::NEQUAL} ('><'|'!=')
656    ;
657
658Subscript returns Subscript::uSubscript  :
659    {Subscript::NOSUB} ':'
660    |{Subscript::SUBSCRIPT} subScript=Expression
661     ;
662     
663ComponentRef returns ComponentRef::uComponentRef  :
664    ComponentReferenceQualified
665    |{ComponentRef::CREF_IDENT}
666    ref=IDENT ('[' subscripts+=Subscript (',' subscripts+=Subscript)* ']')?
667    //  {WILD} 
668    ;
669
670ComponentReferenceQualified returns ComponentRef::uComponentRef  : 
671    {ComponentRef::CREF_QUAL}
672    ref=IDENT ('[' subscripts+=Subscript (',' subscripts+=Subscript)* ']')?
673    '.' componentRef=ComponentRef
674    ;
675   
676/*
677    1) FIXME Fully-qualified path FULLYQUALIFIED
678    2)
679*/
680   
681Path returns Path::uPath :
682    {Path::QUALIFIED} name=IDENT ('.' path=Path|'.*')
683    |{Path::IDENT} name=IDENT
684    ;
685
686//PathStar returns uPath :
687   
688Restriction returns Restriction::uRestriction :
689    {Restriction::R_CLASS} 'class'
690    |{Restriction::R_MODEL} 'model'
691    |{Restriction::R_RECORD} 'record'
692    |{Restriction::R_BLOCK} 'block'
693    |{Restriction::R_CONNECTOR} 'connector'
694    |{Restriction::R_EXP_CONNECTOR} 'expandable' 'connector'
695    |{Restriction::R_TYPE} 'type'
696    |{Restriction::R_PACKAGE} 'package'
697    |{Restriction::R_FUNCTION} 'function'
698    |{Restriction::R_ENUMERATION} 'enumeration'
699    //|{Restriction::R_PREDEFINED_INT} 'Integer'
700    //|{Restriction::R_PREDEFINED_REAL} 'Real'
701    //|{Restriction::R_PREDEFINED_STRING} 'String'
702    //|{Restriction::R_PREDEFINED_BOOL} 'Boolean'
703    ;   
704
705Annotation returns Annotation::uAnnotation:
706    {Annotation::ANNOTATION} 'annotation' '(' elementArgs+=ElementArg (',' elementArgs+=ElementArg)* ')'
707    ;
708
709// CHECK Had to modifiy the comment argument in the EMF model
710Comment returns Comment::uComment:
711    {Comment::COMMENT} (comment=StringComment)? (annotation_=Annotation)?
712    ;
713
714StringComment returns Comment::STRING_COMMENT :
715     comment=STRING
716    ;
717
718ExternalDeclaration returns ExternalDecl::uExternalDecl :
719    {ExternalDecl::EXTERNALDECL} (lang=STRING)? ((output_=ComponentRef '=')? funcName=IDENT
720    '(' args+=Expression (',' args+=Expression)* ')')? (annotation_=Annotation)?
721    ;
722
723/* Not created during parsing
724TimeStamp returns uTimeStamp
725
726    ;
727*/
728
729ForIterators returns Iterators::ForIterators :
730    forIterator+=ForIterator (',' forIterator+=ForIterator)*
731    ;
732
733ForIterator returns Iterators::ForIterator :
734    tuple=ForIteratorTuple
735    ;
736
737ForIteratorTuple returns Iterators::tuple_ForIterator :
738    Ident=IDENT 'in' Exp=Expression
739    ;
740   
741TypeSpecification returns TypeSpec::uTypeSpec :
742    {TypeSpec::TPATH} path=Path (arrayDim=ArrayDim)?
743    //|{TCOMPLEX} path=Path '<' typeSpecs+=TypeSpecification
744    //(',' typeSpecs+=TypeSpecification)* '>'
745    ;
746   
747
748/*------------------------------------------------------------------
749 * LEXER RULES
750 *------------------------------------------------------------------*/
751
752
753
754/*********************************
755    2.3 Strings, numbers, etc.
756**********************************/
757
758terminal ML_COMMENT : '/*' -> '*/';
759terminal SL_COMMENT     : '//' !('\n'|'\r')* ('\r'? '\n')?;
760terminal STRING :
761            '"' ( '\\' ('b'|'t'|'n'|'f'|'r'|'"'|'\''|'\\') | !('\\'|'"') )* '"'
762            //|"'" ( '\\' ('b'|'t'|'n'|'f'|'r'|'"'|"'"|'\\') | !('\\'|"'") )* "'"
763        ;
764terminal WS         : (' '|'\t'|'\r'|'\n')+;
765
766terminal UNSIGNED_REAL returns ecore::EDouble:
767    (('0'..'9')+ '.' ('0'..'9')* (('E'|'e') ('+'|'-')? ('0'..'9')+)? )
768    |(('0'..'9')+ ('E'|'e') ('+'|'-')? ('0'..'9')+)
769    ;
770
771terminal UNSIGNED_INTEGER returns ecore::EInt:
772    ('0'..'9')+
773    ;
774
775terminal BOOL_VAL returns ecore::EBoolean :
776    'true' | 'false'
777    ;
778
779terminal IDENT : ('a'..'z'|'A'..'Z'|'_') ('a'..'z'|'A'..'Z'|'_'|'0'..'9')*;
780
781/*********************************
782    2.2 Operators
783**********************************/
784 
785/*
786terminal    DOT     : '.'           ; 
787terminal    LPAR        : '('       ;
788terminal    RPAR        : ')'       ;
789terminal    LBRACK  : '['       ;
790terminal    RBRACK  : ']'       ;
791terminal    LBRACE  : '{'       ;
792terminal    RBRACE  : '}'       ;
793terminal    EQUALS  : '='       ;
794terminal    ASSIGN  : ':='      ;
795terminal    COMMA       : ','       ;
796terminal    COLON       : ':'       ;
797terminal    SEMICOLON   : ';'       ;
798*/
799  /* elementwise operators */ 
800
801//terminal   PLUS_EW        : '.+'      ; /* Modelica 3.0 */
802//terminal   MINUS_EW       : '.-'      ; /* Modelica 3.0 */   
803//terminal   STAR_EW        : '.*'      ; /* Modelica 3.0 */
804//terminal   SLASH_EW       : './'      ; /* Modelica 3.0 */ 
805//terminal   POWER_EW       : '.^'      ; /* Modelica 3.0 */
806
807/* 
808terminal STAR       : '*'('.')?                 ;
809terminal MINUS      : '-'('.')?                 ;
810terminal PLUS       : '+'('.'|'&')?             ;
811terminal LESS       : '<'('.')?                 ;
812terminal LESSEQ     : '<='('.')?                ;
813terminal LESSGT     : '!='('.')?|'<>'('.')?     ;
814terminal GREATER        : '>'('.')?                 ;
815terminal GREATEREQ  : '>='('.')?                ;
816terminal EQEQ       : '=='('.'|'&')?            ;
817terminal POWER      : '^'('.')?                 ;
818terminal SLASH      : '/'('.')?                 ;
819*/
820terminal ANY_OTHER: .;
Note: See TracBrowser for help on using the repository browser.