1------------------------------------------------------------------------------
2--                                                                          --
3--                            Matreshka Project                             --
4--                                                                          --
5--                          Ada Modeling Framework                          --
6--                                                                          --
7--                        Runtime Library Component                         --
8--                                                                          --
9------------------------------------------------------------------------------
10--                                                                          --
11-- Copyright © 2012-2013, Vadim Godunko <vgodunko@gmail.com>                --
12-- All rights reserved.                                                     --
13--                                                                          --
14-- Redistribution and use in source and binary forms, with or without       --
15-- modification, are permitted provided that the following conditions       --
16-- are met:                                                                 --
17--                                                                          --
18--  * Redistributions of source code must retain the above copyright        --
19--    notice, this list of conditions and the following disclaimer.         --
20--                                                                          --
21--  * Redistributions in binary form must reproduce the above copyright     --
22--    notice, this list of conditions and the following disclaimer in the   --
23--    documentation and/or other materials provided with the distribution.  --
24--                                                                          --
25--  * Neither the name of the Vadim Godunko, IE nor the names of its        --
26--    contributors may be used to endorse or promote products derived from  --
27--    this software without specific prior written permission.              --
28--                                                                          --
29-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS      --
30-- "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT        --
31-- LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR    --
32-- A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT     --
33-- HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,   --
34-- SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED --
35-- TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR   --
36-- PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF   --
37-- LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING     --
38-- NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS       --
39-- SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.             --
40--                                                                          --
41------------------------------------------------------------------------------
42--  $Revision: 3642 $ $Date: 2013-01-07 22:01:06 +0400 (Mon, 07 Jan 2013) $
43------------------------------------------------------------------------------
44--  This file is generated, don't edit it.
45------------------------------------------------------------------------------
46with AMF.Internals.Tables.OCL_Types;
47
48package AMF.Internals.Tables.OCL_Attribute_Mappings is
49
50   pragma Preelaborate;
51
52   OCL_Collection_Offset : constant
53     array (AMF.Internals.Tables.OCL_Types.Element_Kinds,
54            AMF.Internals.CMOF_Element range 48 .. 54)
55       of AMF.Internals.AMF_Collection_Of_Element :=
56        (AMF.Internals.Tables.OCL_Types.E_None =>
57          (others => 0),
58         AMF.Internals.Tables.OCL_Types.E_OCL_Any_Type =>
59          (others => 0),
60         AMF.Internals.Tables.OCL_Types.E_OCL_Association_Class_Call_Exp =>
61          (52     => 4,     --  NavigationCallExp::qualifier
62           others => 0),
63         AMF.Internals.Tables.OCL_Types.E_OCL_Bag_Type =>
64          (others => 0),
65         AMF.Internals.Tables.OCL_Types.E_OCL_Boolean_Literal_Exp =>
66          (others => 0),
67         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Item =>
68          (others => 0),
69         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Literal_Exp =>
70          (48     => 4,     --  CollectionLiteralExp::part
71           others => 0),
72         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Range =>
73          (others => 0),
74         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Type =>
75          (others => 0),
76         AMF.Internals.Tables.OCL_Types.E_OCL_Enum_Literal_Exp =>
77          (others => 0),
78         AMF.Internals.Tables.OCL_Types.E_OCL_Expression_In_Ocl =>
79          (49     => 4,     --  ExpressionInOcl::parameterVariable
80           others => 0),
81         AMF.Internals.Tables.OCL_Types.E_OCL_If_Exp =>
82          (others => 0),
83         AMF.Internals.Tables.OCL_Types.E_OCL_Integer_Literal_Exp =>
84          (others => 0),
85         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Literal_Exp =>
86          (others => 0),
87         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Type =>
88          (others => 0),
89         AMF.Internals.Tables.OCL_Types.E_OCL_Iterate_Exp =>
90          (50     => 4,     --  LoopExp::iterator
91           others => 0),
92         AMF.Internals.Tables.OCL_Types.E_OCL_Iterator_Exp =>
93          (50     => 4,     --  LoopExp::iterator
94           others => 0),
95         AMF.Internals.Tables.OCL_Types.E_OCL_Let_Exp =>
96          (others => 0),
97         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Exp =>
98          (51     => 4,     --  MessageExp::argument
99           others => 0),
100         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Type =>
101          (others => 0),
102         AMF.Internals.Tables.OCL_Types.E_OCL_Null_Literal_Exp =>
103          (others => 0),
104         AMF.Internals.Tables.OCL_Types.E_OCL_Operation_Call_Exp =>
105          (53     => 4,     --  OperationCallExp::argument
106           others => 0),
107         AMF.Internals.Tables.OCL_Types.E_OCL_Ordered_Set_Type =>
108          (others => 0),
109         AMF.Internals.Tables.OCL_Types.E_OCL_Property_Call_Exp =>
110          (52     => 4,     --  NavigationCallExp::qualifier
111           others => 0),
112         AMF.Internals.Tables.OCL_Types.E_OCL_Real_Literal_Exp =>
113          (others => 0),
114         AMF.Internals.Tables.OCL_Types.E_OCL_Sequence_Type =>
115          (others => 0),
116         AMF.Internals.Tables.OCL_Types.E_OCL_Set_Type =>
117          (others => 0),
118         AMF.Internals.Tables.OCL_Types.E_OCL_State_Exp =>
119          (others => 0),
120         AMF.Internals.Tables.OCL_Types.E_OCL_String_Literal_Exp =>
121          (others => 0),
122         AMF.Internals.Tables.OCL_Types.E_OCL_Template_Parameter_Type =>
123          (others => 0),
124         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Exp =>
125          (54     => 4,     --  TupleLiteralExp::part
126           others => 0),
127         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Part =>
128          (others => 0),
129         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Type =>
130          (others => 0),
131         AMF.Internals.Tables.OCL_Types.E_OCL_Type_Exp =>
132          (others => 0),
133         AMF.Internals.Tables.OCL_Types.E_OCL_Unlimited_Natural_Literal_Exp =>
134          (others => 0),
135         AMF.Internals.Tables.OCL_Types.E_OCL_Unspecified_Value_Exp =>
136          (others => 0),
137         AMF.Internals.Tables.OCL_Types.E_OCL_Variable =>
138          (others => 0),
139         AMF.Internals.Tables.OCL_Types.E_OCL_Variable_Exp =>
140          (others => 0),
141         AMF.Internals.Tables.OCL_Types.E_OCL_Void_Type =>
142          (others => 0));
143
144   OCL_Member_Offset : constant
145     array (AMF.Internals.Tables.OCL_Types.Element_Kinds,
146            AMF.Internals.CMOF_Element range 55 .. 93) of Natural :=
147        (AMF.Internals.Tables.OCL_Types.E_None =>
148          (others => 0),
149         AMF.Internals.Tables.OCL_Types.E_OCL_Any_Type =>
150          (others => 0),
151         AMF.Internals.Tables.OCL_Types.E_OCL_Association_Class_Call_Exp =>
152          (81     => 9,     --  NavigationCallExp::navigationSource
153           55     => 10,    --  AssociationClassCallExp::referredAssociationClass
154           57     => 8,     --  CallExp::source
155           others => 0),
156         AMF.Internals.Tables.OCL_Types.E_OCL_Bag_Type =>
157          (62     => 17,    --  CollectionType::elementType
158           others => 0),
159         AMF.Internals.Tables.OCL_Types.E_OCL_Boolean_Literal_Exp =>
160          (56     => 8,     --  BooleanLiteralExp::booleanSymbol
161           others => 0),
162         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Item =>
163          (58     => 8,     --  CollectionItem::item
164           others => 0),
165         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Literal_Exp =>
166          (59     => 8,     --  CollectionLiteralExp::kind
167           others => 0),
168         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Range =>
169          (60     => 8,     --  CollectionRange::first
170           61     => 9,     --  CollectionRange::last
171           others => 0),
172         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Type =>
173          (62     => 17,    --  CollectionType::elementType
174           others => 0),
175         AMF.Internals.Tables.OCL_Types.E_OCL_Enum_Literal_Exp =>
176          (63     => 8,     --  EnumLiteralExp::referredEnumLiteral
177           others => 0),
178         AMF.Internals.Tables.OCL_Types.E_OCL_Expression_In_Ocl =>
179          (64     => 14,    --  ExpressionInOcl::bodyExpression
180           65     => 15,    --  ExpressionInOcl::contextVariable
181           66     => 17,    --  ExpressionInOcl::generatedType
182           67     => 16,    --  ExpressionInOcl::resultVariable
183           others => 0),
184         AMF.Internals.Tables.OCL_Types.E_OCL_If_Exp =>
185          (68     => 8,     --  IfExp::condition
186           69     => 10,    --  IfExp::elseExpression
187           70     => 9,     --  IfExp::thenExpression
188           others => 0),
189         AMF.Internals.Tables.OCL_Types.E_OCL_Integer_Literal_Exp =>
190          (71     => 8,     --  IntegerLiteralExp::integerSymbol
191           others => 0),
192         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Literal_Exp =>
193          (others => 0),
194         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Type =>
195          (others => 0),
196         AMF.Internals.Tables.OCL_Types.E_OCL_Iterate_Exp =>
197          (75     => 9,     --  LoopExp::body
198           72     => 10,    --  IterateExp::result
199           57     => 8,     --  CallExp::source
200           others => 0),
201         AMF.Internals.Tables.OCL_Types.E_OCL_Iterator_Exp =>
202          (75     => 9,     --  LoopExp::body
203           57     => 8,     --  CallExp::source
204           others => 0),
205         AMF.Internals.Tables.OCL_Types.E_OCL_Let_Exp =>
206          (73     => 8,     --  LetExp::in
207           74     => 9,     --  LetExp::variable
208           others => 0),
209         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Exp =>
210          (76     => 9,     --  MessageExp::calledOperation
211           77     => 10,    --  MessageExp::sentSignal
212           78     => 8,     --  MessageExp::target
213           others => 0),
214         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Type =>
215          (79     => 18,    --  MessageType::referredOperation
216           80     => 17,    --  MessageType::referredSignal
217           others => 0),
218         AMF.Internals.Tables.OCL_Types.E_OCL_Null_Literal_Exp =>
219          (others => 0),
220         AMF.Internals.Tables.OCL_Types.E_OCL_Operation_Call_Exp =>
221          (82     => 9,     --  OperationCallExp::referredOperation
222           57     => 8,     --  CallExp::source
223           others => 0),
224         AMF.Internals.Tables.OCL_Types.E_OCL_Ordered_Set_Type =>
225          (62     => 17,    --  CollectionType::elementType
226           others => 0),
227         AMF.Internals.Tables.OCL_Types.E_OCL_Property_Call_Exp =>
228          (81     => 9,     --  NavigationCallExp::navigationSource
229           83     => 10,    --  PropertyCallExp::referredProperty
230           57     => 8,     --  CallExp::source
231           others => 0),
232         AMF.Internals.Tables.OCL_Types.E_OCL_Real_Literal_Exp =>
233          (84     => 8,     --  RealLiteralExp::realSymbol
234           others => 0),
235         AMF.Internals.Tables.OCL_Types.E_OCL_Sequence_Type =>
236          (62     => 17,    --  CollectionType::elementType
237           others => 0),
238         AMF.Internals.Tables.OCL_Types.E_OCL_Set_Type =>
239          (62     => 17,    --  CollectionType::elementType
240           others => 0),
241         AMF.Internals.Tables.OCL_Types.E_OCL_State_Exp =>
242          (85     => 8,     --  StateExp::referredState
243           others => 0),
244         AMF.Internals.Tables.OCL_Types.E_OCL_String_Literal_Exp =>
245          (86     => 8,     --  StringLiteralExp::stringSymbol
246           others => 0),
247         AMF.Internals.Tables.OCL_Types.E_OCL_Template_Parameter_Type =>
248          (87     => 17,    --  TemplateParameterType::specification
249           others => 0),
250         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Exp =>
251          (others => 0),
252         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Part =>
253          (88     => 8,     --  TupleLiteralPart::attribute
254           others => 0),
255         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Type =>
256          (others => 0),
257         AMF.Internals.Tables.OCL_Types.E_OCL_Type_Exp =>
258          (89     => 8,     --  TypeExp::referredType
259           others => 0),
260         AMF.Internals.Tables.OCL_Types.E_OCL_Unlimited_Natural_Literal_Exp =>
261          (90     => 8,     --  UnlimitedNaturalLiteralExp::unlimitedNaturalSymbol
262           others => 0),
263         AMF.Internals.Tables.OCL_Types.E_OCL_Unspecified_Value_Exp =>
264          (others => 0),
265         AMF.Internals.Tables.OCL_Types.E_OCL_Variable =>
266          (91     => 8,     --  Variable::initExpression
267           92     => 9,     --  Variable::representedParameter
268           others => 0),
269         AMF.Internals.Tables.OCL_Types.E_OCL_Variable_Exp =>
270          (93     => 8,     --  VariableExp::referredVariable
271           others => 0),
272         AMF.Internals.Tables.OCL_Types.E_OCL_Void_Type =>
273          (others => 0));
274
275   UML_Collection_Offset : constant
276     array (AMF.Internals.Tables.OCL_Types.Element_Kinds,
277            AMF.Internals.CMOF_Element range 243 .. 482)
278       of AMF.Internals.AMF_Collection_Of_Element :=
279        (AMF.Internals.Tables.OCL_Types.E_None =>
280          (others => 0),
281         AMF.Internals.Tables.OCL_Types.E_OCL_Any_Type =>
282          (296    => 13,    --  Classifier::attribute
283           400    => 3,     --  NamedElement::clientDependency
284           297    => 14,    --  Classifier::collaborationUse
285           401    => 4,     --  Namespace::elementImport
286           298    => 15,    --  Classifier::feature
287           299    => 16,    --  Classifier::general
288           300    => 17,    --  Classifier::generalization
289           402    => 5,     --  Namespace::importedMember
290           301    => 18,    --  Classifier::inheritedMember
291           403    => 6,     --  Namespace::member
292           347    => 1,     --  Element::ownedComment
293           348    => 2,     --  Element::ownedElement
294           404    => 7,     --  Namespace::ownedMember
295           405    => 8,     --  Namespace::ownedRule
296           302    => 19,    --  Classifier::ownedUseCase
297           406    => 9,     --  Namespace::packageImport
298           303    => 20,    --  Classifier::powertypeExtent
299           304    => 21,    --  Classifier::redefinedClassifier
300           439    => 11,    --  RedefinableElement::redefinedElement
301           440    => 12,    --  RedefinableElement::redefinitionContext
302           305    => 22,    --  Classifier::substitution
303           472    => 10,    --  TemplateableElement::templateBinding
304           306    => 23,    --  Classifier::useCase
305           others => 0),
306         AMF.Internals.Tables.OCL_Types.E_OCL_Association_Class_Call_Exp =>
307          (400    => 3,     --  NamedElement::clientDependency
308           347    => 1,     --  Element::ownedComment
309           348    => 2,     --  Element::ownedElement
310           others => 0),
311         AMF.Internals.Tables.OCL_Types.E_OCL_Bag_Type =>
312          (296    => 13,    --  Classifier::attribute
313           400    => 3,     --  NamedElement::clientDependency
314           297    => 14,    --  Classifier::collaborationUse
315           401    => 4,     --  Namespace::elementImport
316           298    => 15,    --  Classifier::feature
317           299    => 16,    --  Classifier::general
318           300    => 17,    --  Classifier::generalization
319           402    => 5,     --  Namespace::importedMember
320           301    => 18,    --  Classifier::inheritedMember
321           403    => 6,     --  Namespace::member
322           334    => 24,    --  DataType::ownedAttribute
323           347    => 1,     --  Element::ownedComment
324           348    => 2,     --  Element::ownedElement
325           404    => 7,     --  Namespace::ownedMember
326           335    => 25,    --  DataType::ownedOperation
327           405    => 8,     --  Namespace::ownedRule
328           302    => 19,    --  Classifier::ownedUseCase
329           406    => 9,     --  Namespace::packageImport
330           303    => 20,    --  Classifier::powertypeExtent
331           304    => 21,    --  Classifier::redefinedClassifier
332           439    => 11,    --  RedefinableElement::redefinedElement
333           440    => 12,    --  RedefinableElement::redefinitionContext
334           305    => 22,    --  Classifier::substitution
335           472    => 10,    --  TemplateableElement::templateBinding
336           306    => 23,    --  Classifier::useCase
337           others => 0),
338         AMF.Internals.Tables.OCL_Types.E_OCL_Boolean_Literal_Exp =>
339          (400    => 3,     --  NamedElement::clientDependency
340           347    => 1,     --  Element::ownedComment
341           348    => 2,     --  Element::ownedElement
342           others => 0),
343         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Item =>
344          (400    => 3,     --  NamedElement::clientDependency
345           347    => 1,     --  Element::ownedComment
346           348    => 2,     --  Element::ownedElement
347           others => 0),
348         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Literal_Exp =>
349          (400    => 3,     --  NamedElement::clientDependency
350           347    => 1,     --  Element::ownedComment
351           348    => 2,     --  Element::ownedElement
352           others => 0),
353         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Range =>
354          (400    => 3,     --  NamedElement::clientDependency
355           347    => 1,     --  Element::ownedComment
356           348    => 2,     --  Element::ownedElement
357           others => 0),
358         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Type =>
359          (296    => 13,    --  Classifier::attribute
360           400    => 3,     --  NamedElement::clientDependency
361           297    => 14,    --  Classifier::collaborationUse
362           401    => 4,     --  Namespace::elementImport
363           298    => 15,    --  Classifier::feature
364           299    => 16,    --  Classifier::general
365           300    => 17,    --  Classifier::generalization
366           402    => 5,     --  Namespace::importedMember
367           301    => 18,    --  Classifier::inheritedMember
368           403    => 6,     --  Namespace::member
369           334    => 24,    --  DataType::ownedAttribute
370           347    => 1,     --  Element::ownedComment
371           348    => 2,     --  Element::ownedElement
372           404    => 7,     --  Namespace::ownedMember
373           335    => 25,    --  DataType::ownedOperation
374           405    => 8,     --  Namespace::ownedRule
375           302    => 19,    --  Classifier::ownedUseCase
376           406    => 9,     --  Namespace::packageImport
377           303    => 20,    --  Classifier::powertypeExtent
378           304    => 21,    --  Classifier::redefinedClassifier
379           439    => 11,    --  RedefinableElement::redefinedElement
380           440    => 12,    --  RedefinableElement::redefinitionContext
381           305    => 22,    --  Classifier::substitution
382           472    => 10,    --  TemplateableElement::templateBinding
383           306    => 23,    --  Classifier::useCase
384           others => 0),
385         AMF.Internals.Tables.OCL_Types.E_OCL_Enum_Literal_Exp =>
386          (400    => 3,     --  NamedElement::clientDependency
387           347    => 1,     --  Element::ownedComment
388           348    => 2,     --  Element::ownedElement
389           others => 0),
390         AMF.Internals.Tables.OCL_Types.E_OCL_Expression_In_Ocl =>
391          (400    => 3,     --  NamedElement::clientDependency
392           347    => 1,     --  Element::ownedComment
393           348    => 2,     --  Element::ownedElement
394           others => 0),
395         AMF.Internals.Tables.OCL_Types.E_OCL_If_Exp =>
396          (400    => 3,     --  NamedElement::clientDependency
397           347    => 1,     --  Element::ownedComment
398           348    => 2,     --  Element::ownedElement
399           others => 0),
400         AMF.Internals.Tables.OCL_Types.E_OCL_Integer_Literal_Exp =>
401          (400    => 3,     --  NamedElement::clientDependency
402           347    => 1,     --  Element::ownedComment
403           348    => 2,     --  Element::ownedElement
404           others => 0),
405         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Literal_Exp =>
406          (400    => 3,     --  NamedElement::clientDependency
407           347    => 1,     --  Element::ownedComment
408           348    => 2,     --  Element::ownedElement
409           others => 0),
410         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Type =>
411          (296    => 13,    --  Classifier::attribute
412           400    => 3,     --  NamedElement::clientDependency
413           297    => 14,    --  Classifier::collaborationUse
414           401    => 4,     --  Namespace::elementImport
415           298    => 15,    --  Classifier::feature
416           299    => 16,    --  Classifier::general
417           300    => 17,    --  Classifier::generalization
418           402    => 5,     --  Namespace::importedMember
419           301    => 18,    --  Classifier::inheritedMember
420           403    => 6,     --  Namespace::member
421           347    => 1,     --  Element::ownedComment
422           348    => 2,     --  Element::ownedElement
423           404    => 7,     --  Namespace::ownedMember
424           405    => 8,     --  Namespace::ownedRule
425           302    => 19,    --  Classifier::ownedUseCase
426           406    => 9,     --  Namespace::packageImport
427           303    => 20,    --  Classifier::powertypeExtent
428           304    => 21,    --  Classifier::redefinedClassifier
429           439    => 11,    --  RedefinableElement::redefinedElement
430           440    => 12,    --  RedefinableElement::redefinitionContext
431           305    => 22,    --  Classifier::substitution
432           472    => 10,    --  TemplateableElement::templateBinding
433           306    => 23,    --  Classifier::useCase
434           others => 0),
435         AMF.Internals.Tables.OCL_Types.E_OCL_Iterate_Exp =>
436          (400    => 3,     --  NamedElement::clientDependency
437           347    => 1,     --  Element::ownedComment
438           348    => 2,     --  Element::ownedElement
439           others => 0),
440         AMF.Internals.Tables.OCL_Types.E_OCL_Iterator_Exp =>
441          (400    => 3,     --  NamedElement::clientDependency
442           347    => 1,     --  Element::ownedComment
443           348    => 2,     --  Element::ownedElement
444           others => 0),
445         AMF.Internals.Tables.OCL_Types.E_OCL_Let_Exp =>
446          (400    => 3,     --  NamedElement::clientDependency
447           347    => 1,     --  Element::ownedComment
448           348    => 2,     --  Element::ownedElement
449           others => 0),
450         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Exp =>
451          (400    => 3,     --  NamedElement::clientDependency
452           347    => 1,     --  Element::ownedComment
453           348    => 2,     --  Element::ownedElement
454           others => 0),
455         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Type =>
456          (296    => 13,    --  Classifier::attribute
457           400    => 3,     --  NamedElement::clientDependency
458           297    => 14,    --  Classifier::collaborationUse
459           401    => 4,     --  Namespace::elementImport
460           298    => 15,    --  Classifier::feature
461           299    => 16,    --  Classifier::general
462           300    => 17,    --  Classifier::generalization
463           402    => 5,     --  Namespace::importedMember
464           301    => 18,    --  Classifier::inheritedMember
465           403    => 6,     --  Namespace::member
466           347    => 1,     --  Element::ownedComment
467           348    => 2,     --  Element::ownedElement
468           404    => 7,     --  Namespace::ownedMember
469           405    => 8,     --  Namespace::ownedRule
470           302    => 19,    --  Classifier::ownedUseCase
471           406    => 9,     --  Namespace::packageImport
472           303    => 20,    --  Classifier::powertypeExtent
473           304    => 21,    --  Classifier::redefinedClassifier
474           439    => 11,    --  RedefinableElement::redefinedElement
475           440    => 12,    --  RedefinableElement::redefinitionContext
476           305    => 22,    --  Classifier::substitution
477           472    => 10,    --  TemplateableElement::templateBinding
478           306    => 23,    --  Classifier::useCase
479           others => 0),
480         AMF.Internals.Tables.OCL_Types.E_OCL_Null_Literal_Exp =>
481          (400    => 3,     --  NamedElement::clientDependency
482           347    => 1,     --  Element::ownedComment
483           348    => 2,     --  Element::ownedElement
484           others => 0),
485         AMF.Internals.Tables.OCL_Types.E_OCL_Operation_Call_Exp =>
486          (400    => 3,     --  NamedElement::clientDependency
487           347    => 1,     --  Element::ownedComment
488           348    => 2,     --  Element::ownedElement
489           others => 0),
490         AMF.Internals.Tables.OCL_Types.E_OCL_Ordered_Set_Type =>
491          (296    => 13,    --  Classifier::attribute
492           400    => 3,     --  NamedElement::clientDependency
493           297    => 14,    --  Classifier::collaborationUse
494           401    => 4,     --  Namespace::elementImport
495           298    => 15,    --  Classifier::feature
496           299    => 16,    --  Classifier::general
497           300    => 17,    --  Classifier::generalization
498           402    => 5,     --  Namespace::importedMember
499           301    => 18,    --  Classifier::inheritedMember
500           403    => 6,     --  Namespace::member
501           334    => 24,    --  DataType::ownedAttribute
502           347    => 1,     --  Element::ownedComment
503           348    => 2,     --  Element::ownedElement
504           404    => 7,     --  Namespace::ownedMember
505           335    => 25,    --  DataType::ownedOperation
506           405    => 8,     --  Namespace::ownedRule
507           302    => 19,    --  Classifier::ownedUseCase
508           406    => 9,     --  Namespace::packageImport
509           303    => 20,    --  Classifier::powertypeExtent
510           304    => 21,    --  Classifier::redefinedClassifier
511           439    => 11,    --  RedefinableElement::redefinedElement
512           440    => 12,    --  RedefinableElement::redefinitionContext
513           305    => 22,    --  Classifier::substitution
514           472    => 10,    --  TemplateableElement::templateBinding
515           306    => 23,    --  Classifier::useCase
516           others => 0),
517         AMF.Internals.Tables.OCL_Types.E_OCL_Property_Call_Exp =>
518          (400    => 3,     --  NamedElement::clientDependency
519           347    => 1,     --  Element::ownedComment
520           348    => 2,     --  Element::ownedElement
521           others => 0),
522         AMF.Internals.Tables.OCL_Types.E_OCL_Real_Literal_Exp =>
523          (400    => 3,     --  NamedElement::clientDependency
524           347    => 1,     --  Element::ownedComment
525           348    => 2,     --  Element::ownedElement
526           others => 0),
527         AMF.Internals.Tables.OCL_Types.E_OCL_Sequence_Type =>
528          (296    => 13,    --  Classifier::attribute
529           400    => 3,     --  NamedElement::clientDependency
530           297    => 14,    --  Classifier::collaborationUse
531           401    => 4,     --  Namespace::elementImport
532           298    => 15,    --  Classifier::feature
533           299    => 16,    --  Classifier::general
534           300    => 17,    --  Classifier::generalization
535           402    => 5,     --  Namespace::importedMember
536           301    => 18,    --  Classifier::inheritedMember
537           403    => 6,     --  Namespace::member
538           334    => 24,    --  DataType::ownedAttribute
539           347    => 1,     --  Element::ownedComment
540           348    => 2,     --  Element::ownedElement
541           404    => 7,     --  Namespace::ownedMember
542           335    => 25,    --  DataType::ownedOperation
543           405    => 8,     --  Namespace::ownedRule
544           302    => 19,    --  Classifier::ownedUseCase
545           406    => 9,     --  Namespace::packageImport
546           303    => 20,    --  Classifier::powertypeExtent
547           304    => 21,    --  Classifier::redefinedClassifier
548           439    => 11,    --  RedefinableElement::redefinedElement
549           440    => 12,    --  RedefinableElement::redefinitionContext
550           305    => 22,    --  Classifier::substitution
551           472    => 10,    --  TemplateableElement::templateBinding
552           306    => 23,    --  Classifier::useCase
553           others => 0),
554         AMF.Internals.Tables.OCL_Types.E_OCL_Set_Type =>
555          (296    => 13,    --  Classifier::attribute
556           400    => 3,     --  NamedElement::clientDependency
557           297    => 14,    --  Classifier::collaborationUse
558           401    => 4,     --  Namespace::elementImport
559           298    => 15,    --  Classifier::feature
560           299    => 16,    --  Classifier::general
561           300    => 17,    --  Classifier::generalization
562           402    => 5,     --  Namespace::importedMember
563           301    => 18,    --  Classifier::inheritedMember
564           403    => 6,     --  Namespace::member
565           334    => 24,    --  DataType::ownedAttribute
566           347    => 1,     --  Element::ownedComment
567           348    => 2,     --  Element::ownedElement
568           404    => 7,     --  Namespace::ownedMember
569           335    => 25,    --  DataType::ownedOperation
570           405    => 8,     --  Namespace::ownedRule
571           302    => 19,    --  Classifier::ownedUseCase
572           406    => 9,     --  Namespace::packageImport
573           303    => 20,    --  Classifier::powertypeExtent
574           304    => 21,    --  Classifier::redefinedClassifier
575           439    => 11,    --  RedefinableElement::redefinedElement
576           440    => 12,    --  RedefinableElement::redefinitionContext
577           305    => 22,    --  Classifier::substitution
578           472    => 10,    --  TemplateableElement::templateBinding
579           306    => 23,    --  Classifier::useCase
580           others => 0),
581         AMF.Internals.Tables.OCL_Types.E_OCL_State_Exp =>
582          (400    => 3,     --  NamedElement::clientDependency
583           347    => 1,     --  Element::ownedComment
584           348    => 2,     --  Element::ownedElement
585           others => 0),
586         AMF.Internals.Tables.OCL_Types.E_OCL_String_Literal_Exp =>
587          (400    => 3,     --  NamedElement::clientDependency
588           347    => 1,     --  Element::ownedComment
589           348    => 2,     --  Element::ownedElement
590           others => 0),
591         AMF.Internals.Tables.OCL_Types.E_OCL_Template_Parameter_Type =>
592          (296    => 13,    --  Classifier::attribute
593           400    => 3,     --  NamedElement::clientDependency
594           297    => 14,    --  Classifier::collaborationUse
595           401    => 4,     --  Namespace::elementImport
596           298    => 15,    --  Classifier::feature
597           299    => 16,    --  Classifier::general
598           300    => 17,    --  Classifier::generalization
599           402    => 5,     --  Namespace::importedMember
600           301    => 18,    --  Classifier::inheritedMember
601           403    => 6,     --  Namespace::member
602           347    => 1,     --  Element::ownedComment
603           348    => 2,     --  Element::ownedElement
604           404    => 7,     --  Namespace::ownedMember
605           405    => 8,     --  Namespace::ownedRule
606           302    => 19,    --  Classifier::ownedUseCase
607           406    => 9,     --  Namespace::packageImport
608           303    => 20,    --  Classifier::powertypeExtent
609           304    => 21,    --  Classifier::redefinedClassifier
610           439    => 11,    --  RedefinableElement::redefinedElement
611           440    => 12,    --  RedefinableElement::redefinitionContext
612           305    => 22,    --  Classifier::substitution
613           472    => 10,    --  TemplateableElement::templateBinding
614           306    => 23,    --  Classifier::useCase
615           others => 0),
616         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Exp =>
617          (400    => 3,     --  NamedElement::clientDependency
618           347    => 1,     --  Element::ownedComment
619           348    => 2,     --  Element::ownedElement
620           others => 0),
621         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Part =>
622          (400    => 3,     --  NamedElement::clientDependency
623           347    => 1,     --  Element::ownedComment
624           348    => 2,     --  Element::ownedElement
625           others => 0),
626         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Type =>
627          (296    => 13,    --  Classifier::attribute
628           400    => 3,     --  NamedElement::clientDependency
629           297    => 14,    --  Classifier::collaborationUse
630           401    => 4,     --  Namespace::elementImport
631           298    => 15,    --  Classifier::feature
632           299    => 16,    --  Classifier::general
633           300    => 17,    --  Classifier::generalization
634           402    => 5,     --  Namespace::importedMember
635           301    => 18,    --  Classifier::inheritedMember
636           403    => 6,     --  Namespace::member
637           334    => 24,    --  DataType::ownedAttribute
638           347    => 1,     --  Element::ownedComment
639           348    => 2,     --  Element::ownedElement
640           404    => 7,     --  Namespace::ownedMember
641           335    => 25,    --  DataType::ownedOperation
642           405    => 8,     --  Namespace::ownedRule
643           302    => 19,    --  Classifier::ownedUseCase
644           406    => 9,     --  Namespace::packageImport
645           303    => 20,    --  Classifier::powertypeExtent
646           304    => 21,    --  Classifier::redefinedClassifier
647           439    => 11,    --  RedefinableElement::redefinedElement
648           440    => 12,    --  RedefinableElement::redefinitionContext
649           305    => 22,    --  Classifier::substitution
650           472    => 10,    --  TemplateableElement::templateBinding
651           306    => 23,    --  Classifier::useCase
652           others => 0),
653         AMF.Internals.Tables.OCL_Types.E_OCL_Type_Exp =>
654          (400    => 3,     --  NamedElement::clientDependency
655           347    => 1,     --  Element::ownedComment
656           348    => 2,     --  Element::ownedElement
657           others => 0),
658         AMF.Internals.Tables.OCL_Types.E_OCL_Unlimited_Natural_Literal_Exp =>
659          (400    => 3,     --  NamedElement::clientDependency
660           347    => 1,     --  Element::ownedComment
661           348    => 2,     --  Element::ownedElement
662           others => 0),
663         AMF.Internals.Tables.OCL_Types.E_OCL_Unspecified_Value_Exp =>
664          (400    => 3,     --  NamedElement::clientDependency
665           347    => 1,     --  Element::ownedComment
666           348    => 2,     --  Element::ownedElement
667           others => 0),
668         AMF.Internals.Tables.OCL_Types.E_OCL_Variable =>
669          (400    => 3,     --  NamedElement::clientDependency
670           347    => 1,     --  Element::ownedComment
671           348    => 2,     --  Element::ownedElement
672           others => 0),
673         AMF.Internals.Tables.OCL_Types.E_OCL_Variable_Exp =>
674          (400    => 3,     --  NamedElement::clientDependency
675           347    => 1,     --  Element::ownedComment
676           348    => 2,     --  Element::ownedElement
677           others => 0),
678         AMF.Internals.Tables.OCL_Types.E_OCL_Void_Type =>
679          (296    => 13,    --  Classifier::attribute
680           400    => 3,     --  NamedElement::clientDependency
681           297    => 14,    --  Classifier::collaborationUse
682           401    => 4,     --  Namespace::elementImport
683           298    => 15,    --  Classifier::feature
684           299    => 16,    --  Classifier::general
685           300    => 17,    --  Classifier::generalization
686           402    => 5,     --  Namespace::importedMember
687           301    => 18,    --  Classifier::inheritedMember
688           403    => 6,     --  Namespace::member
689           347    => 1,     --  Element::ownedComment
690           348    => 2,     --  Element::ownedElement
691           404    => 7,     --  Namespace::ownedMember
692           405    => 8,     --  Namespace::ownedRule
693           302    => 19,    --  Classifier::ownedUseCase
694           406    => 9,     --  Namespace::packageImport
695           303    => 20,    --  Classifier::powertypeExtent
696           304    => 21,    --  Classifier::redefinedClassifier
697           439    => 11,    --  RedefinableElement::redefinedElement
698           440    => 12,    --  RedefinableElement::redefinitionContext
699           305    => 22,    --  Classifier::substitution
700           472    => 10,    --  TemplateableElement::templateBinding
701           306    => 23,    --  Classifier::useCase
702           others => 0));
703
704   UML_Member_Offset : constant
705     array (AMF.Internals.Tables.OCL_Types.Element_Kinds,
706            AMF.Internals.CMOF_Element range 483 .. 866) of Natural :=
707        (AMF.Internals.Tables.OCL_Types.E_None =>
708          (others => 0),
709         AMF.Internals.Tables.OCL_Types.E_OCL_Any_Type =>
710          (530    => 12,    --  Classifier::isAbstract
711           531    => 13,    --  Classifier::isFinalSpecialization
712           772    => 11,    --  RedefinableElement::isLeaf
713           669    => 2,     --  NamedElement::name
714           670    => 3,     --  NamedElement::nameExpression
715           671    => 4,     --  NamedElement::namespace
716           532    => 14,    --  Classifier::ownedTemplateSignature
717           831    => 10,    --  TemplateableElement::ownedTemplateSignature
718           577    => 1,     --  Element::owner
719           718    => 8,     --  ParameterableElement::owningTemplateParameter
720           853    => 7,     --  Type::package
721           672    => 5,     --  NamedElement::qualifiedName
722           533    => 15,    --  Classifier::representation
723           534    => 16,    --  Classifier::templateParameter
724           719    => 9,     --  ParameterableElement::templateParameter
725           673    => 6,     --  NamedElement::visibility
726           710    => 6,     --  PackageableElement::visibility
727           others => 0),
728         AMF.Internals.Tables.OCL_Types.E_OCL_Association_Class_Call_Exp =>
729          (669    => 2,     --  NamedElement::name
730           670    => 3,     --  NamedElement::nameExpression
731           671    => 4,     --  NamedElement::namespace
732           577    => 1,     --  Element::owner
733           672    => 5,     --  NamedElement::qualifiedName
734           854    => 7,     --  TypedElement::type
735           673    => 6,     --  NamedElement::visibility
736           others => 0),
737         AMF.Internals.Tables.OCL_Types.E_OCL_Bag_Type =>
738          (530    => 12,    --  Classifier::isAbstract
739           531    => 13,    --  Classifier::isFinalSpecialization
740           772    => 11,    --  RedefinableElement::isLeaf
741           669    => 2,     --  NamedElement::name
742           670    => 3,     --  NamedElement::nameExpression
743           671    => 4,     --  NamedElement::namespace
744           532    => 14,    --  Classifier::ownedTemplateSignature
745           831    => 10,    --  TemplateableElement::ownedTemplateSignature
746           577    => 1,     --  Element::owner
747           718    => 8,     --  ParameterableElement::owningTemplateParameter
748           853    => 7,     --  Type::package
749           672    => 5,     --  NamedElement::qualifiedName
750           533    => 15,    --  Classifier::representation
751           534    => 16,    --  Classifier::templateParameter
752           719    => 9,     --  ParameterableElement::templateParameter
753           673    => 6,     --  NamedElement::visibility
754           710    => 6,     --  PackageableElement::visibility
755           others => 0),
756         AMF.Internals.Tables.OCL_Types.E_OCL_Boolean_Literal_Exp =>
757          (669    => 2,     --  NamedElement::name
758           670    => 3,     --  NamedElement::nameExpression
759           671    => 4,     --  NamedElement::namespace
760           577    => 1,     --  Element::owner
761           672    => 5,     --  NamedElement::qualifiedName
762           854    => 7,     --  TypedElement::type
763           673    => 6,     --  NamedElement::visibility
764           others => 0),
765         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Item =>
766          (669    => 2,     --  NamedElement::name
767           670    => 3,     --  NamedElement::nameExpression
768           671    => 4,     --  NamedElement::namespace
769           577    => 1,     --  Element::owner
770           672    => 5,     --  NamedElement::qualifiedName
771           854    => 7,     --  TypedElement::type
772           673    => 6,     --  NamedElement::visibility
773           others => 0),
774         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Literal_Exp =>
775          (669    => 2,     --  NamedElement::name
776           670    => 3,     --  NamedElement::nameExpression
777           671    => 4,     --  NamedElement::namespace
778           577    => 1,     --  Element::owner
779           672    => 5,     --  NamedElement::qualifiedName
780           854    => 7,     --  TypedElement::type
781           673    => 6,     --  NamedElement::visibility
782           others => 0),
783         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Range =>
784          (669    => 2,     --  NamedElement::name
785           670    => 3,     --  NamedElement::nameExpression
786           671    => 4,     --  NamedElement::namespace
787           577    => 1,     --  Element::owner
788           672    => 5,     --  NamedElement::qualifiedName
789           854    => 7,     --  TypedElement::type
790           673    => 6,     --  NamedElement::visibility
791           others => 0),
792         AMF.Internals.Tables.OCL_Types.E_OCL_Collection_Type =>
793          (530    => 12,    --  Classifier::isAbstract
794           531    => 13,    --  Classifier::isFinalSpecialization
795           772    => 11,    --  RedefinableElement::isLeaf
796           669    => 2,     --  NamedElement::name
797           670    => 3,     --  NamedElement::nameExpression
798           671    => 4,     --  NamedElement::namespace
799           532    => 14,    --  Classifier::ownedTemplateSignature
800           831    => 10,    --  TemplateableElement::ownedTemplateSignature
801           577    => 1,     --  Element::owner
802           718    => 8,     --  ParameterableElement::owningTemplateParameter
803           853    => 7,     --  Type::package
804           672    => 5,     --  NamedElement::qualifiedName
805           533    => 15,    --  Classifier::representation
806           534    => 16,    --  Classifier::templateParameter
807           719    => 9,     --  ParameterableElement::templateParameter
808           673    => 6,     --  NamedElement::visibility
809           710    => 6,     --  PackageableElement::visibility
810           others => 0),
811         AMF.Internals.Tables.OCL_Types.E_OCL_Enum_Literal_Exp =>
812          (669    => 2,     --  NamedElement::name
813           670    => 3,     --  NamedElement::nameExpression
814           671    => 4,     --  NamedElement::namespace
815           577    => 1,     --  Element::owner
816           672    => 5,     --  NamedElement::qualifiedName
817           854    => 7,     --  TypedElement::type
818           673    => 6,     --  NamedElement::visibility
819           others => 0),
820         AMF.Internals.Tables.OCL_Types.E_OCL_Expression_In_Ocl =>
821          (687    => 10,    --  OpaqueExpression::behavior
822           688    => 11,    --  OpaqueExpression::body
823           689    => 12,    --  OpaqueExpression::language
824           669    => 2,     --  NamedElement::name
825           670    => 3,     --  NamedElement::nameExpression
826           671    => 4,     --  NamedElement::namespace
827           577    => 1,     --  Element::owner
828           718    => 8,     --  ParameterableElement::owningTemplateParameter
829           672    => 5,     --  NamedElement::qualifiedName
830           690    => 13,    --  OpaqueExpression::result
831           719    => 9,     --  ParameterableElement::templateParameter
832           854    => 7,     --  TypedElement::type
833           673    => 6,     --  NamedElement::visibility
834           710    => 6,     --  PackageableElement::visibility
835           others => 0),
836         AMF.Internals.Tables.OCL_Types.E_OCL_If_Exp =>
837          (669    => 2,     --  NamedElement::name
838           670    => 3,     --  NamedElement::nameExpression
839           671    => 4,     --  NamedElement::namespace
840           577    => 1,     --  Element::owner
841           672    => 5,     --  NamedElement::qualifiedName
842           854    => 7,     --  TypedElement::type
843           673    => 6,     --  NamedElement::visibility
844           others => 0),
845         AMF.Internals.Tables.OCL_Types.E_OCL_Integer_Literal_Exp =>
846          (669    => 2,     --  NamedElement::name
847           670    => 3,     --  NamedElement::nameExpression
848           671    => 4,     --  NamedElement::namespace
849           577    => 1,     --  Element::owner
850           672    => 5,     --  NamedElement::qualifiedName
851           854    => 7,     --  TypedElement::type
852           673    => 6,     --  NamedElement::visibility
853           others => 0),
854         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Literal_Exp =>
855          (669    => 2,     --  NamedElement::name
856           670    => 3,     --  NamedElement::nameExpression
857           671    => 4,     --  NamedElement::namespace
858           577    => 1,     --  Element::owner
859           672    => 5,     --  NamedElement::qualifiedName
860           854    => 7,     --  TypedElement::type
861           673    => 6,     --  NamedElement::visibility
862           others => 0),
863         AMF.Internals.Tables.OCL_Types.E_OCL_Invalid_Type =>
864          (530    => 12,    --  Classifier::isAbstract
865           531    => 13,    --  Classifier::isFinalSpecialization
866           772    => 11,    --  RedefinableElement::isLeaf
867           669    => 2,     --  NamedElement::name
868           670    => 3,     --  NamedElement::nameExpression
869           671    => 4,     --  NamedElement::namespace
870           532    => 14,    --  Classifier::ownedTemplateSignature
871           831    => 10,    --  TemplateableElement::ownedTemplateSignature
872           577    => 1,     --  Element::owner
873           718    => 8,     --  ParameterableElement::owningTemplateParameter
874           853    => 7,     --  Type::package
875           672    => 5,     --  NamedElement::qualifiedName
876           533    => 15,    --  Classifier::representation
877           534    => 16,    --  Classifier::templateParameter
878           719    => 9,     --  ParameterableElement::templateParameter
879           673    => 6,     --  NamedElement::visibility
880           710    => 6,     --  PackageableElement::visibility
881           others => 0),
882         AMF.Internals.Tables.OCL_Types.E_OCL_Iterate_Exp =>
883          (669    => 2,     --  NamedElement::name
884           670    => 3,     --  NamedElement::nameExpression
885           671    => 4,     --  NamedElement::namespace
886           577    => 1,     --  Element::owner
887           672    => 5,     --  NamedElement::qualifiedName
888           854    => 7,     --  TypedElement::type
889           673    => 6,     --  NamedElement::visibility
890           others => 0),
891         AMF.Internals.Tables.OCL_Types.E_OCL_Iterator_Exp =>
892          (669    => 2,     --  NamedElement::name
893           670    => 3,     --  NamedElement::nameExpression
894           671    => 4,     --  NamedElement::namespace
895           577    => 1,     --  Element::owner
896           672    => 5,     --  NamedElement::qualifiedName
897           854    => 7,     --  TypedElement::type
898           673    => 6,     --  NamedElement::visibility
899           others => 0),
900         AMF.Internals.Tables.OCL_Types.E_OCL_Let_Exp =>
901          (669    => 2,     --  NamedElement::name
902           670    => 3,     --  NamedElement::nameExpression
903           671    => 4,     --  NamedElement::namespace
904           577    => 1,     --  Element::owner
905           672    => 5,     --  NamedElement::qualifiedName
906           854    => 7,     --  TypedElement::type
907           673    => 6,     --  NamedElement::visibility
908           others => 0),
909         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Exp =>
910          (669    => 2,     --  NamedElement::name
911           670    => 3,     --  NamedElement::nameExpression
912           671    => 4,     --  NamedElement::namespace
913           577    => 1,     --  Element::owner
914           672    => 5,     --  NamedElement::qualifiedName
915           854    => 7,     --  TypedElement::type
916           673    => 6,     --  NamedElement::visibility
917           others => 0),
918         AMF.Internals.Tables.OCL_Types.E_OCL_Message_Type =>
919          (530    => 12,    --  Classifier::isAbstract
920           531    => 13,    --  Classifier::isFinalSpecialization
921           772    => 11,    --  RedefinableElement::isLeaf
922           669    => 2,     --  NamedElement::name
923           670    => 3,     --  NamedElement::nameExpression
924           671    => 4,     --  NamedElement::namespace
925           532    => 14,    --  Classifier::ownedTemplateSignature
926           831    => 10,    --  TemplateableElement::ownedTemplateSignature
927           577    => 1,     --  Element::owner
928           718    => 8,     --  ParameterableElement::owningTemplateParameter
929           853    => 7,     --  Type::package
930           672    => 5,     --  NamedElement::qualifiedName
931           533    => 15,    --  Classifier::representation
932           534    => 16,    --  Classifier::templateParameter
933           719    => 9,     --  ParameterableElement::templateParameter
934           673    => 6,     --  NamedElement::visibility
935           710    => 6,     --  PackageableElement::visibility
936           others => 0),
937         AMF.Internals.Tables.OCL_Types.E_OCL_Null_Literal_Exp =>
938          (669    => 2,     --  NamedElement::name
939           670    => 3,     --  NamedElement::nameExpression
940           671    => 4,     --  NamedElement::namespace
941           577    => 1,     --  Element::owner
942           672    => 5,     --  NamedElement::qualifiedName
943           854    => 7,     --  TypedElement::type
944           673    => 6,     --  NamedElement::visibility
945           others => 0),
946         AMF.Internals.Tables.OCL_Types.E_OCL_Operation_Call_Exp =>
947          (669    => 2,     --  NamedElement::name
948           670    => 3,     --  NamedElement::nameExpression
949           671    => 4,     --  NamedElement::namespace
950           577    => 1,     --  Element::owner
951           672    => 5,     --  NamedElement::qualifiedName
952           854    => 7,     --  TypedElement::type
953           673    => 6,     --  NamedElement::visibility
954           others => 0),
955         AMF.Internals.Tables.OCL_Types.E_OCL_Ordered_Set_Type =>
956          (530    => 12,    --  Classifier::isAbstract
957           531    => 13,    --  Classifier::isFinalSpecialization
958           772    => 11,    --  RedefinableElement::isLeaf
959           669    => 2,     --  NamedElement::name
960           670    => 3,     --  NamedElement::nameExpression
961           671    => 4,     --  NamedElement::namespace
962           532    => 14,    --  Classifier::ownedTemplateSignature
963           831    => 10,    --  TemplateableElement::ownedTemplateSignature
964           577    => 1,     --  Element::owner
965           718    => 8,     --  ParameterableElement::owningTemplateParameter
966           853    => 7,     --  Type::package
967           672    => 5,     --  NamedElement::qualifiedName
968           533    => 15,    --  Classifier::representation
969           534    => 16,    --  Classifier::templateParameter
970           719    => 9,     --  ParameterableElement::templateParameter
971           673    => 6,     --  NamedElement::visibility
972           710    => 6,     --  PackageableElement::visibility
973           others => 0),
974         AMF.Internals.Tables.OCL_Types.E_OCL_Property_Call_Exp =>
975          (669    => 2,     --  NamedElement::name
976           670    => 3,     --  NamedElement::nameExpression
977           671    => 4,     --  NamedElement::namespace
978           577    => 1,     --  Element::owner
979           672    => 5,     --  NamedElement::qualifiedName
980           854    => 7,     --  TypedElement::type
981           673    => 6,     --  NamedElement::visibility
982           others => 0),
983         AMF.Internals.Tables.OCL_Types.E_OCL_Real_Literal_Exp =>
984          (669    => 2,     --  NamedElement::name
985           670    => 3,     --  NamedElement::nameExpression
986           671    => 4,     --  NamedElement::namespace
987           577    => 1,     --  Element::owner
988           672    => 5,     --  NamedElement::qualifiedName
989           854    => 7,     --  TypedElement::type
990           673    => 6,     --  NamedElement::visibility
991           others => 0),
992         AMF.Internals.Tables.OCL_Types.E_OCL_Sequence_Type =>
993          (530    => 12,    --  Classifier::isAbstract
994           531    => 13,    --  Classifier::isFinalSpecialization
995           772    => 11,    --  RedefinableElement::isLeaf
996           669    => 2,     --  NamedElement::name
997           670    => 3,     --  NamedElement::nameExpression
998           671    => 4,     --  NamedElement::namespace
999           532    => 14,    --  Classifier::ownedTemplateSignature
1000           831    => 10,    --  TemplateableElement::ownedTemplateSignature
1001           577    => 1,     --  Element::owner
1002           718    => 8,     --  ParameterableElement::owningTemplateParameter
1003           853    => 7,     --  Type::package
1004           672    => 5,     --  NamedElement::qualifiedName
1005           533    => 15,    --  Classifier::representation
1006           534    => 16,    --  Classifier::templateParameter
1007           719    => 9,     --  ParameterableElement::templateParameter
1008           673    => 6,     --  NamedElement::visibility
1009           710    => 6,     --  PackageableElement::visibility
1010           others => 0),
1011         AMF.Internals.Tables.OCL_Types.E_OCL_Set_Type =>
1012          (530    => 12,    --  Classifier::isAbstract
1013           531    => 13,    --  Classifier::isFinalSpecialization
1014           772    => 11,    --  RedefinableElement::isLeaf
1015           669    => 2,     --  NamedElement::name
1016           670    => 3,     --  NamedElement::nameExpression
1017           671    => 4,     --  NamedElement::namespace
1018           532    => 14,    --  Classifier::ownedTemplateSignature
1019           831    => 10,    --  TemplateableElement::ownedTemplateSignature
1020           577    => 1,     --  Element::owner
1021           718    => 8,     --  ParameterableElement::owningTemplateParameter
1022           853    => 7,     --  Type::package
1023           672    => 5,     --  NamedElement::qualifiedName
1024           533    => 15,    --  Classifier::representation
1025           534    => 16,    --  Classifier::templateParameter
1026           719    => 9,     --  ParameterableElement::templateParameter
1027           673    => 6,     --  NamedElement::visibility
1028           710    => 6,     --  PackageableElement::visibility
1029           others => 0),
1030         AMF.Internals.Tables.OCL_Types.E_OCL_State_Exp =>
1031          (669    => 2,     --  NamedElement::name
1032           670    => 3,     --  NamedElement::nameExpression
1033           671    => 4,     --  NamedElement::namespace
1034           577    => 1,     --  Element::owner
1035           672    => 5,     --  NamedElement::qualifiedName
1036           854    => 7,     --  TypedElement::type
1037           673    => 6,     --  NamedElement::visibility
1038           others => 0),
1039         AMF.Internals.Tables.OCL_Types.E_OCL_String_Literal_Exp =>
1040          (669    => 2,     --  NamedElement::name
1041           670    => 3,     --  NamedElement::nameExpression
1042           671    => 4,     --  NamedElement::namespace
1043           577    => 1,     --  Element::owner
1044           672    => 5,     --  NamedElement::qualifiedName
1045           854    => 7,     --  TypedElement::type
1046           673    => 6,     --  NamedElement::visibility
1047           others => 0),
1048         AMF.Internals.Tables.OCL_Types.E_OCL_Template_Parameter_Type =>
1049          (530    => 12,    --  Classifier::isAbstract
1050           531    => 13,    --  Classifier::isFinalSpecialization
1051           772    => 11,    --  RedefinableElement::isLeaf
1052           669    => 2,     --  NamedElement::name
1053           670    => 3,     --  NamedElement::nameExpression
1054           671    => 4,     --  NamedElement::namespace
1055           532    => 14,    --  Classifier::ownedTemplateSignature
1056           831    => 10,    --  TemplateableElement::ownedTemplateSignature
1057           577    => 1,     --  Element::owner
1058           718    => 8,     --  ParameterableElement::owningTemplateParameter
1059           853    => 7,     --  Type::package
1060           672    => 5,     --  NamedElement::qualifiedName
1061           533    => 15,    --  Classifier::representation
1062           534    => 16,    --  Classifier::templateParameter
1063           719    => 9,     --  ParameterableElement::templateParameter
1064           673    => 6,     --  NamedElement::visibility
1065           710    => 6,     --  PackageableElement::visibility
1066           others => 0),
1067         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Exp =>
1068          (669    => 2,     --  NamedElement::name
1069           670    => 3,     --  NamedElement::nameExpression
1070           671    => 4,     --  NamedElement::namespace
1071           577    => 1,     --  Element::owner
1072           672    => 5,     --  NamedElement::qualifiedName
1073           854    => 7,     --  TypedElement::type
1074           673    => 6,     --  NamedElement::visibility
1075           others => 0),
1076         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Literal_Part =>
1077          (669    => 2,     --  NamedElement::name
1078           670    => 3,     --  NamedElement::nameExpression
1079           671    => 4,     --  NamedElement::namespace
1080           577    => 1,     --  Element::owner
1081           672    => 5,     --  NamedElement::qualifiedName
1082           854    => 7,     --  TypedElement::type
1083           673    => 6,     --  NamedElement::visibility
1084           others => 0),
1085         AMF.Internals.Tables.OCL_Types.E_OCL_Tuple_Type =>
1086          (530    => 12,    --  Classifier::isAbstract
1087           531    => 13,    --  Classifier::isFinalSpecialization
1088           772    => 11,    --  RedefinableElement::isLeaf
1089           669    => 2,     --  NamedElement::name
1090           670    => 3,     --  NamedElement::nameExpression
1091           671    => 4,     --  NamedElement::namespace
1092           532    => 14,    --  Classifier::ownedTemplateSignature
1093           831    => 10,    --  TemplateableElement::ownedTemplateSignature
1094           577    => 1,     --  Element::owner
1095           718    => 8,     --  ParameterableElement::owningTemplateParameter
1096           853    => 7,     --  Type::package
1097           672    => 5,     --  NamedElement::qualifiedName
1098           533    => 15,    --  Classifier::representation
1099           534    => 16,    --  Classifier::templateParameter
1100           719    => 9,     --  ParameterableElement::templateParameter
1101           673    => 6,     --  NamedElement::visibility
1102           710    => 6,     --  PackageableElement::visibility
1103           others => 0),
1104         AMF.Internals.Tables.OCL_Types.E_OCL_Type_Exp =>
1105          (669    => 2,     --  NamedElement::name
1106           670    => 3,     --  NamedElement::nameExpression
1107           671    => 4,     --  NamedElement::namespace
1108           577    => 1,     --  Element::owner
1109           672    => 5,     --  NamedElement::qualifiedName
1110           854    => 7,     --  TypedElement::type
1111           673    => 6,     --  NamedElement::visibility
1112           others => 0),
1113         AMF.Internals.Tables.OCL_Types.E_OCL_Unlimited_Natural_Literal_Exp =>
1114          (669    => 2,     --  NamedElement::name
1115           670    => 3,     --  NamedElement::nameExpression
1116           671    => 4,     --  NamedElement::namespace
1117           577    => 1,     --  Element::owner
1118           672    => 5,     --  NamedElement::qualifiedName
1119           854    => 7,     --  TypedElement::type
1120           673    => 6,     --  NamedElement::visibility
1121           others => 0),
1122         AMF.Internals.Tables.OCL_Types.E_OCL_Unspecified_Value_Exp =>
1123          (669    => 2,     --  NamedElement::name
1124           670    => 3,     --  NamedElement::nameExpression
1125           671    => 4,     --  NamedElement::namespace
1126           577    => 1,     --  Element::owner
1127           672    => 5,     --  NamedElement::qualifiedName
1128           854    => 7,     --  TypedElement::type
1129           673    => 6,     --  NamedElement::visibility
1130           others => 0),
1131         AMF.Internals.Tables.OCL_Types.E_OCL_Variable =>
1132          (669    => 2,     --  NamedElement::name
1133           670    => 3,     --  NamedElement::nameExpression
1134           671    => 4,     --  NamedElement::namespace
1135           577    => 1,     --  Element::owner
1136           672    => 5,     --  NamedElement::qualifiedName
1137           854    => 7,     --  TypedElement::type
1138           673    => 6,     --  NamedElement::visibility
1139           others => 0),
1140         AMF.Internals.Tables.OCL_Types.E_OCL_Variable_Exp =>
1141          (669    => 2,     --  NamedElement::name
1142           670    => 3,     --  NamedElement::nameExpression
1143           671    => 4,     --  NamedElement::namespace
1144           577    => 1,     --  Element::owner
1145           672    => 5,     --  NamedElement::qualifiedName
1146           854    => 7,     --  TypedElement::type
1147           673    => 6,     --  NamedElement::visibility
1148           others => 0),
1149         AMF.Internals.Tables.OCL_Types.E_OCL_Void_Type =>
1150          (530    => 12,    --  Classifier::isAbstract
1151           531    => 13,    --  Classifier::isFinalSpecialization
1152           772    => 11,    --  RedefinableElement::isLeaf
1153           669    => 2,     --  NamedElement::name
1154           670    => 3,     --  NamedElement::nameExpression
1155           671    => 4,     --  NamedElement::namespace
1156           532    => 14,    --  Classifier::ownedTemplateSignature
1157           831    => 10,    --  TemplateableElement::ownedTemplateSignature
1158           577    => 1,     --  Element::owner
1159           718    => 8,     --  ParameterableElement::owningTemplateParameter
1160           853    => 7,     --  Type::package
1161           672    => 5,     --  NamedElement::qualifiedName
1162           533    => 15,    --  Classifier::representation
1163           534    => 16,    --  Classifier::templateParameter
1164           719    => 9,     --  ParameterableElement::templateParameter
1165           673    => 6,     --  NamedElement::visibility
1166           710    => 6,     --  PackageableElement::visibility
1167           others => 0));
1168
1169end AMF.Internals.Tables.OCL_Attribute_Mappings;
1170