~ubuntu-branches/ubuntu/hoary/scilab/hoary

« back to all changes in this revision

Viewing changes to ocaml/parseTree.mli

  • Committer: Bazaar Package Importer
  • Author(s): Torsten Werner
  • Date: 2005-01-09 22:58:21 UTC
  • mfrom: (1.1.1 upstream)
  • Revision ID: james.westby@ubuntu.com-20050109225821-473xr8vhgugxxx5j
Tags: 3.0-12
changed configure.in to build scilab's own malloc.o, closes: #255869

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
(** This module defines the data structures necessary to hold parse trees built
 
2
by the parser (see Parser module) *)
 
3
 
 
4
type t = StoredDefinition of within * definition list
 
5
and within = Within of name option | NotWithin
 
6
and definition = Definition of final * class_definition
 
7
and final = Final | NotFinal
 
8
and class_definition =
 
9
    ClassDefinition of class_kind * ident * encapsulated * partial *
 
10
      class_specifier
 
11
and class_kind =
 
12
    Class
 
13
  | Model
 
14
  | Record
 
15
  | Connector
 
16
  | Type
 
17
  | Package
 
18
  | Function
 
19
and encapsulated = Encapsulated | NotEncapsulated
 
20
and partial = Partial | NotPartial
 
21
and class_specifier =
 
22
    Specifier of string_comment * composition * ident
 
23
  | ShortSpecifier of base_prefix * name * array_subscripts *
 
24
      class_modification option * comment
 
25
  | Enumeration of enumeration_literal list * comment
 
26
and base_prefix = type_prefix
 
27
and enumeration_literal = EnumerationLiteral of ident * comment
 
28
and composition =
 
29
    Composition of element list * other_elements list * externalll option
 
30
and element =
 
31
    AnnotationElement of annotation
 
32
  | ImportClause of import_clause
 
33
  | ExtendsClause of extends_clause
 
34
  | ClassDefinitionElement of class_definition * final * dynamic_scope
 
35
  | ComponentClauseElement of component_clause * final * dynamic_scope
 
36
  | ReplaceableClassDefinition of class_definition *
 
37
      (constraining_clause * comment) option * final * dynamic_scope
 
38
  | ReplaceableComponentClause of component_clause *
 
39
      (constraining_clause * comment) option * final * dynamic_scope
 
40
and dynamic_scope = Inner | Outer | NoDynamicScope
 
41
and extends_clause = name * class_modification option
 
42
and constraining_clause = extends_clause
 
43
and other_elements =
 
44
    Public of element list
 
45
  | Protected of element list
 
46
  | EquationClauseElement of equation_clause
 
47
  | AlgorithmClauseElement of algorithm_clause
 
48
and externalll =
 
49
    External of string option * external_function_call option *
 
50
      annotation option
 
51
and external_function_call =
 
52
    ExternalFunctionCall of component_reference option * ident *
 
53
      expression list
 
54
and import_clause =
 
55
    NewIdentifier of ident * name * comment
 
56
  | Identifier of name * comment
 
57
  | AllIdentifiers of name * comment
 
58
and component_clause =
 
59
    ComponentClause of type_prefix * type_specifier * array_subscripts *
 
60
      component_declaration list
 
61
and type_prefix =
 
62
    TypePrefix of flow option * variability option * inout option
 
63
and flow = Flow
 
64
and variability = Discrete | Parameter | Constant
 
65
and inout = Input | Output
 
66
and type_specifier = name
 
67
and component_declaration = ComponentDeclaration of declaration * comment
 
68
and declaration = ident * array_subscripts * modification option
 
69
and modification =
 
70
    Modification of class_modification * expression option
 
71
  | Eq of expression
 
72
  | ColEq of expression
 
73
and class_modification = ClassModification of argument list
 
74
and argument =
 
75
    ElementModification of each * final * component_reference *
 
76
      modification * string_comment
 
77
  | ElementRedeclaration of each * final * redeclaration
 
78
and each = Each | NotEach
 
79
and redeclaration =
 
80
    Redeclaration of replaceable * redeclared_element *
 
81
      (constraining_clause * comment) option
 
82
and replaceable = Replaceable | NotReplaceable
 
83
and redeclared_element =
 
84
    RedeclaredClassDefinition of class_definition
 
85
  | RedeclaredComponentClause of type_prefix * type_specifier *
 
86
      component_declaration
 
87
and equation_clause = EquationClause of initial * equation_or_annotation list
 
88
and equation_or_annotation =
 
89
    Equation of equation * comment
 
90
  | EquationAnnotation of annotation
 
91
and algorithm_clause =
 
92
    AlgorithmClause of initial * algorithm_or_annotation list
 
93
and algorithm_or_annotation =
 
94
    Algorithm of algorithm * comment
 
95
  | AlgorithmAnnotation of annotation
 
96
and initial = Initial | NotInitial
 
97
and equation =
 
98
    Equality of expression * expression
 
99
  | ConditionalEquationE of (expression * equation list) list * equation list
 
100
  | ForClauseE of for_indices * equation list
 
101
  | ConnectClause of component_reference * component_reference
 
102
  | WhenClauseE of (expression * equation list) list
 
103
  | FunctionCallE of component_reference * function_arguments option
 
104
and algorithm =
 
105
    Assignment of component_reference * expression
 
106
  | FunctionCallA of component_reference * function_arguments option
 
107
  | MultipleAssignment of expression list * component_reference *
 
108
      function_arguments option
 
109
  | ConditionalEquationA of (expression * algorithm list) list *
 
110
      algorithm list
 
111
  | ForClauseA of for_indices * algorithm list
 
112
  | WhileClause of expression * algorithm list
 
113
  | WhenClauseA of (expression * algorithm list) list
 
114
and for_indices = (ident * expression option) list
 
115
and expression =
 
116
    Addition of expression * expression
 
117
  | And of expression * expression
 
118
  | Division of expression * expression
 
119
  | End
 
120
  | Equals of expression * expression
 
121
  | ExpressionList of expression array
 
122
  | False
 
123
  | FunctionCall of component_reference * function_arguments option
 
124
  | GreaterEqualThan of expression * expression
 
125
  | GreaterThan of expression * expression
 
126
  | If of (expression * expression) list * expression
 
127
  | Integer of string
 
128
  | LessEqualThan of expression * expression
 
129
  | LessThan of expression * expression
 
130
  | ArrayConcatenation of expression list list
 
131
  | Minus of expression
 
132
  | Multiplication of expression * expression
 
133
  | Not of expression
 
134
  | NotEquals of expression * expression
 
135
  | Or of expression * expression
 
136
  | Plus of expression
 
137
  | Power of expression * expression
 
138
  | Range of expression * expression * expression option
 
139
  | Real of string
 
140
  | Reference of component_reference
 
141
  | String of string
 
142
  | Subtraction of expression * expression
 
143
  | True
 
144
  | VectorOrRecord of function_arguments
 
145
and ident = string
 
146
and name = ident list
 
147
and component_reference = (ident * array_subscripts) list
 
148
and function_arguments =
 
149
    ArgList of expression list * for_indices option
 
150
  | NamedArgList of (ident * expression) list * for_indices option
 
151
and array_subscripts = array_subscript array
 
152
and array_subscript = All | Subscript of expression
 
153
and comment = Comment of string_comment * annotation option
 
154
and string_comment = StringComment of string list
 
155
and annotation = Annotation of class_modification