1(*
2 *  Modelicac
3 *
4 *  Copyright (C) 2005 - 2007 Imagine S.A.
5 *  For more information or commercial use please contact us at www.amesim.com
6 *
7 *  This program is free software; you can redistribute it and/or
8 *  modify it under the terms of the GNU General Public License
9 *  as published by the Free Software Foundation; either version 2
10 *  of the License, or (at your option) any later version.
11 *
12 *  This program is distributed in the hope that it will be useful,
13 *  but WITHOUT ANY WARRANTY; without even the implied warranty of
14 *  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15 *  GNU General Public License for more details.
16 *
17 *  You should have received a copy of the GNU General Public License
18 *  along with this program; if not, write to the Free Software
19 *  Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
20 *
21 *)
22
23type t =
24  | StoredDefinition of within * definition list
25
26and within =
27  | Within of name option
28  | NotWithin
29
30and definition =
31  | Definition of final * class_definition
32
33and final =
34  | Final
35  | NotFinal
36
37and class_definition =
38  | ClassDefinition of class_kind * ident * encapsulated * partial *
39      class_specifier
40
41and class_kind =
42  | Class
43  | Model
44  | Record
45  | Connector
46  | Type
47  | Package
48  | Function
49
50and encapsulated =
51  | Encapsulated
52  | NotEncapsulated
53
54and partial =
55  | Partial
56  | NotPartial
57
58and class_specifier =
59  | Specifier of string_comment * composition * ident
60  | ShortSpecifier of base_prefix * name * array_subscripts *
61      class_modification option * comment
62  | Enumeration of enumeration_literal list * comment
63
64and base_prefix = type_prefix
65
66and enumeration_literal =
67  | EnumerationLiteral of ident * comment
68
69and composition =
70  | Composition of element list * other_elements list * externalll option
71
72and element =
73  | AnnotationElement of annotation
74  | ImportClause of import_clause
75  | ExtendsClause of extends_clause
76  | ClassDefinitionElement of class_definition * final * dynamic_scope
77  | ComponentClauseElement of component_clause * final * dynamic_scope
78  | ReplaceableClassDefinition of class_definition *
79      (constraining_clause * comment) option * final * dynamic_scope
80  | ReplaceableComponentClause of component_clause *
81      (constraining_clause * comment) option * final * dynamic_scope
82
83and dynamic_scope =
84  | Inner
85  | Outer
86  | NoDynamicScope
87
88and extends_clause = name * class_modification option
89
90and constraining_clause = extends_clause
91
92and other_elements =
93  | Public of element list
94  | Protected of element list
95  | EquationClauseElement of equation_clause
96  | AlgorithmClauseElement of algorithm_clause
97
98and externalll =
99  | External of string option * external_function_call option *
100      annotation option
101
102and external_function_call =
103  | ExternalFunctionCall of component_reference option * ident *
104      expression list
105
106and import_clause =
107  | NewIdentifier of ident * name * comment
108  | Identifier of name * comment
109  | AllIdentifiers of name * comment
110
111and component_clause =
112  | ComponentClause of type_prefix * type_specifier *
113      array_subscripts * component_declaration list
114
115and type_prefix =
116  | TypePrefix of flow option * variability option * inout option
117
118and flow =
119  | Flow
120
121and variability =
122  | Discrete
123  | Parameter
124  | Constant
125
126and inout =
127  | Input
128  | Output
129
130and type_specifier = name
131
132and component_declaration =
133  | ComponentDeclaration of declaration * comment
134
135and declaration = ident * array_subscripts * modification option
136
137and modification =
138  | Modification of class_modification * expression option
139  | Eq of expression
140  | ColEq of expression
141
142and class_modification =
143  | ClassModification of argument list
144
145and argument =
146  | ElementModification of each * final * component_reference *
147      modification * string_comment
148  | ElementRedeclaration of each * final * redeclaration
149
150and each =
151  | Each
152  | NotEach
153
154and redeclaration =
155  | Redeclaration of replaceable * redeclared_element *
156      (constraining_clause * comment) option
157
158and replaceable =
159  | Replaceable
160  | NotReplaceable
161
162and redeclared_element =
163  | RedeclaredClassDefinition of class_definition
164  | RedeclaredComponentClause of type_prefix * type_specifier *
165      component_declaration
166
167and equation_clause =
168  | EquationClause of initial * equation_or_annotation list
169
170and equation_or_annotation =
171  | Equation of equation * comment
172  | EquationAnnotation of annotation
173
174and algorithm_clause =
175  | AlgorithmClause of initial * algorithm_or_annotation list
176
177and algorithm_or_annotation =
178  | Algorithm of algorithm * comment
179  | AlgorithmAnnotation of annotation
180
181and initial =
182  | Initial
183  | NotInitial
184
185and equation =
186  | Equality of (* simple *) expression * expression
187  | ConditionalEquationE of (expression * equation list) list * equation list
188  | ForClauseE of for_indices * equation list
189  | ConnectClause of component_reference * component_reference
190  | WhenClauseE of (expression * equation list) list
191  | FunctionCallE of component_reference * function_arguments option
192
193and algorithm =
194  | Assignment of component_reference * expression
195  | FunctionCallA of component_reference * function_arguments option
196  | MultipleAssignment of expression list * component_reference *
197      function_arguments option
198  | ConditionalEquationA of (expression * algorithm list) list * algorithm list
199  | ForClauseA of for_indices * algorithm list
200  | WhileClause of expression * algorithm list
201  | WhenClauseA of (expression * algorithm list) list
202
203and for_indices = (ident * expression option) list
204
205and expression =
206  | Addition of expression * expression
207  | And of expression * expression
208  | Division of expression * expression
209  | End
210  | Equals of expression * expression
211  | ExpressionList of expression array
212  | False
213  | FunctionCall of component_reference * function_arguments option
214  | GreaterEqualThan of expression * expression
215  | GreaterThan of expression * expression
216  | If of (expression * expression) list * expression
217  | Integer of string
218  | LessEqualThan of expression * expression
219  | LessThan of expression * expression
220  | ArrayConcatenation of expression list list
221  | Minus of expression
222  | Multiplication of expression * expression
223  | Not of expression
224  | NotEquals of expression * expression
225  | Or of expression * expression
226  | Plus of expression
227  | Power of expression * expression
228  | Range of expression * expression * expression option
229  | Real of string
230  | Reference of component_reference
231  | String of string
232  | Subtraction of expression * expression
233  | True
234  | VectorOrRecord of function_arguments
235
236and ident = string
237
238and name = ident list
239
240and component_reference = (ident * array_subscripts) list
241
242and function_arguments =
243  | ArgList of expression list * for_indices option
244  | NamedArgList of (ident * expression) list * for_indices option
245
246and array_subscripts = array_subscript array
247
248and array_subscript =
249  | All
250  | Subscript of expression
251
252and comment =
253  | Comment of string_comment * annotation option
254
255and string_comment =
256  | StringComment of string list
257
258and annotation =
259  | Annotation of class_modification
260