2 (* ========================================================================= *)
4 (* Symbol file reading module for the .NET to Gardens Point Component *)
5 (* Pascal Symbols tool. *)
6 (* Copyright (c) Siu-Yuen Chan 2001. *)
8 (* This module reads Gardens Point Component Pascal (GPCP) symbol files *)
9 (* and stores all meta information read into METASTORE (defined by *)
10 (* MetaStore module). *)
11 (* ========================================================================= *)
22 (* ========================================================================= *
23 // Collected syntax ---
25 // SymFile = Header [String (falSy | truSy | <other attribute>)]
26 // {Import | Constant | Variable | Type | Procedure}
28 // -- optional String is external name.
29 // -- falSy ==> Java class
30 // -- truSy ==> Java interface
32 // Header = magic modSy Name.
33 // VersionName= numSy longint numSy longint numSy longint.
34 // -- mj# mn# bld rv# 8xbyte extract
35 // Import = impSy Name [String] Key.
36 // -- optional string is explicit external name of class
37 // Constant = conSy Name Literal.
38 // Variable = varSy Name TypeOrd.
39 // Type = typSy Name TypeOrd.
40 // Procedure = prcSy Name [String] FormalType.
41 // -- optional string is explicit external name of procedure
42 // Method = mthSy Name byte byte TypeOrd [String] FormalType.
43 // -- optional string is explicit external name of method
44 // FormalType = [retSy TypeOrd] frmSy {parSy byte TypeOrd} endFm.
45 // -- optional phrase is return type for proper procedures
47 // TypeHeader = tDefS Ord [fromS Ord Name].
48 // -- optional phrase occurs if:
49 // -- type not from this module, i.e. indirect export
50 // TypeList = start { Array | Record | Pointer | ProcType } close.
51 // Array = TypeHeader arrSy TypeOrd (Byte | Number | <empty>) endAr.
52 // -- nullable phrase is array length for fixed length arrays
53 // Pointer = TypeHeader ptrSy TypeOrd.
54 // Event = TypeHeader evtSy FormalType.
55 // ProcType = TypeHeader pTpSy FormalType.
56 // Record = TypeHeader recSy recAtt [truSy | falSy]
57 // [basSy TypeOrd] [iFcSy {basSy TypeOrd}]
58 // {Name TypeOrd} {Method} endRc.
59 // -- truSy ==> is an extension of external interface
60 // -- falSy ==> is an extension of external class
61 // -- basSy option defines base type, if not ANY / j.l.Object
62 // NamedType = TypeHeader
63 // Name = namSy byte UTFstring.
64 // Literal = Number | String | Set | Char | Real | falSy | truSy.
66 // String = strSy UTFstring.
67 // Number = numSy longint.
68 // Real = fltSy ieee-double.
69 // Set = setSy integer.
70 // Key = keySy integer..
71 // Char = chrSy unicode character.
73 // Notes on the syntax:
74 // All record types must have a Name field, even though this is often
75 // redundant. The issue is that every record type (including those that
76 // are anonymous in CP) corresponds to a IR class, and the definer
77 // and the user of the class _must_ agree on the IR name of the class.
78 // The same reasoning applies to procedure types, which must have equal
79 // interface names in all modules.
80 // ======================================================================== *)
84 modSy
= ORD('H'
); namSy
= ORD('$'
); bytSy
= ORD('
\');
85 numSy
= ORD('
#'
); chrSy
= ORD('c'
); strSy
= ORD('s'
);
86 fltSy
= ORD('r'
); falSy
= ORD('
0'
); truSy
= ORD('
1'
);
87 impSy
= ORD('I'
); setSy
= ORD('S'
); keySy
= ORD('K'
);
88 conSy
= ORD('C'
); typSy
= ORD('T'
); tDefS
= ORD('t'
);
89 prcSy
= ORD('P'
); retSy
= ORD('R'
); mthSy
= ORD('M'
);
90 varSy
= ORD('V'
); parSy
= ORD('p'
); start
= ORD('
&'
);
91 close
= ORD('
!'
); recSy
= ORD('
{'
); endRc
= ORD('
}'
);
92 frmSy
= ORD('
('
); fromS
= ORD('@'
); endFm
= ORD('
)'
);
93 arrSy
= ORD('
['
); endAr
= ORD('
]'
); pTpSy
= ORD('%'
);
94 ptrSy
= ORD('^'
); basSy
= ORD('
+'
); eTpSy
= ORD('e'
);
95 iFcSy
= ORD('~'
); evtSy
= ORD('v'
);
98 tOffset
* = 16; (* backward compatibility with JavaVersion *)
106 CONST (* record attributes *)
107 noAtt
* = ORD(MS
.noAtt
); (* no attribute *)
108 abstr
* = ORD(MS
.Rabstr
); (* Is ABSTRACT *)
109 limit
* = ORD(MS
.Rlimit
); (* Is LIMIT *)
110 extns
* = ORD(MS
.Rextns
); (* Is EXTENSIBLE *)
111 iFace
* = ORD(MS
.RiFace
); (* Is INTERFACE *)
112 nnarg
* = ORD(MS
.Rnnarg
); (* Has NO NoArg Constructor ( cannot use NEW() ) *)
113 valTp
* = ORD(MS
.RvalTp
); (* ValueType *)
118 CharOpen* = POINTER TO ARRAY OF CHAR;
120 CharOpen
* = ST
.CharOpen
;
126 a
: POINTER TO ARRAY OF MS
.Type
;
129 ScopeSeq
= POINTER TO
133 a
: POINTER TO ARRAY OF MS
.Namespace
;
141 sSym
: INTEGER; (* the symbol read in *)
142 cAtt
: CHAR; (* character attribute *)
143 iAtt
: INTEGER; (* integer attribute *)
144 lAtt
: LONGINT; (* long attribute *)
145 rAtt
: REAL; (* real attribute *)
146 sAtt
: ARRAY 128 OF CHAR; (* string attribute *)
152 (* for building temporary formal list *)
161 PROCEDURE InitTypeSeq(seq
: TypeSeq
; capacity
: INTEGER);
163 NEW(seq
.a
, capacity
);
164 seq
.high
:= capacity
-1;
169 PROCEDURE AppendType(VAR seq
: TypeSeq
; elem
: MS
.Type
);
171 temp
: POINTER TO ARRAY OF MS
.Type
;
176 ELSIF seq
.tide
> seq
.high
THEN (* must expand *)
178 seq
.high
:= seq
.high
* 2 + 1;
179 NEW(seq
.a
, (seq
.high
+1));
180 FOR i
:= 0 TO seq
.tide
-1 DO seq
.a
[i
] := temp
[i
] END;
182 seq
.a
[seq
.tide
] := elem
; INC(seq
.tide
);
186 PROCEDURE InitScopeSeq(seq
: ScopeSeq
; capacity
: INTEGER);
188 NEW(seq
.a
, capacity
);
189 seq
.high
:= capacity
-1;
194 PROCEDURE AppendScope(VAR seq
: ScopeSeq
; elem
: MS
.Namespace
);
196 temp
: POINTER TO ARRAY OF MS
.Namespace
;
200 InitScopeSeq(seq
, 2);
201 ELSIF seq
.tide
> seq
.high
THEN (* must expand *)
203 seq
.high
:= seq
.high
* 2 + 1;
204 NEW(seq
.a
, (seq
.high
+1));
205 FOR i
:= 0 TO seq
.tide
-1 DO seq
.a
[i
] := temp
[i
] END;
207 seq
.a
[seq
.tide
] := elem
; INC(seq
.tide
);
211 PROCEDURE (rd
: Reader
) Read(): INTEGER, NEW;
213 RETURN GF
.readByte(rd
.file
);
217 PROCEDURE (rd
: Reader
) ReadChar(): CHAR, NEW;
219 RETURN CHR(rd
.Read() * 256 + rd
.Read());
223 PROCEDURE (rd
: Reader
) ReadInt(): INTEGER, NEW;
224 BEGIN [UNCHECKED_ARITHMETIC
]
225 (* overflow checking off here *)
226 RETURN ((rd
.Read() * 256 + rd
.Read()) * 256 + rd
.Read()) * 256 + rd
.Read();
230 PROCEDURE (rd
: Reader
) ReadLong(): LONGINT, NEW;
234 BEGIN [UNCHECKED_ARITHMETIC
]
235 (* overflow checking off here *)
237 FOR index
:= 1 TO 7 DO
238 result
:= result
* 256 + rd
.Read();
244 PROCEDURE (rd
: Reader
) ReadReal(): REAL, NEW;
248 result
:= rd
.ReadLong();
249 RETURN RTS
.longBitsToReal(result
);
253 PROCEDURE (rd
: Reader
) ReadOrd(): INTEGER, NEW;
258 IF chr
<= 07FH
THEN RETURN chr
;
261 RETURN chr
+ rd
.Read() * 128;
266 PROCEDURE (rd
: Reader
) ReadUTF(OUT nam
: ARRAY OF CHAR), NEW;
268 bad
= "Bad UTF-8 string";
276 bNm
:= rd
.Read() * 256 + rd
.Read();
277 FOR idx
:= 0 TO bNm
-1 DO
279 IF chr
<= 07FH
THEN (* [0xxxxxxx] *)
280 nam
[num
] := CHR(chr
); INC(num
);
281 ELSIF chr
DIV 32 = 06H
THEN (* [110xxxxx,10xxxxxx] *)
282 bNm
:= chr
MOD 32 * 64;
284 IF chr
DIV 64 = 02H
THEN
285 nam
[num
] := CHR(bNm
+ chr
MOD 64); INC(num
);
289 ELSIF chr
DIV 16 = 0EH
THEN (* [1110xxxx,10xxxxxx,10xxxxxx] *)
290 bNm
:= chr
MOD 16 * 64;
292 IF chr
DIV 64 = 02H
THEN
293 bNm
:= (bNm
+ chr
MOD 64) * 64;
295 IF chr
DIV 64 = 02H
THEN
296 nam
[num
] := CHR(bNm
+ chr
MOD 64); INC(num
);
311 PROCEDURE (rd
: Reader
) GetSym(), NEW;
313 rd
.sSym
:= rd
.Read();
316 rd
.iAtt
:= rd
.Read(); rd
.ReadUTF(rd
.sAtt
);
319 | retSy
, fromS
, tDefS
, basSy
:
320 rd
.iAtt
:= rd
.ReadOrd();
322 rd
.iAtt
:= rd
.Read();
324 rd
.iAtt
:= rd
.ReadInt();
326 rd
.lAtt
:= rd
.ReadLong();
328 rd
.rAtt
:= rd
.ReadReal();
330 rd
.cAtt
:= rd
.ReadChar();
331 ELSE (* nothing to do *)
336 PROCEDURE (rd
: Reader
) Abandon(), NEW;
338 RTS
.Throw(ST
.StrCat(ST
.ToChrOpen("Bad symbol file format - "),
339 ST
.ToChrOpen(GF
.getFullPathName(rd
.file
))));
343 PROCEDURE (rd
: Reader
) ReadPast(sym
: INTEGER), NEW;
345 IF rd
.sSym
# sym
THEN rd
.Abandon(); END;
350 PROCEDURE NewReader
*(file
: GF
.FILE
) : Reader
;
358 InitTypeSeq(new
.tArray
, 8);
359 InitScopeSeq(new
.sArray
, 8);
365 PROCEDURE (rd
: Reader
) TypeOf(ord
: INTEGER): MS
.Type
, NEW;
371 IF ord
< tOffset
THEN (* builtin type *)
372 rslt
:= MS
.baseTypeArray
[ord
];
374 rslt
:= MS
.MakeDummyPrimitive(ord
);
377 ELSIF ord
- tOffset
< rd
.tArray
.tide
THEN (* type already read *)
378 RETURN rd
.tArray
.a
[ord
- tOffset
];
380 indx
:= rd
.tArray
.tide
+ tOffset
;
382 (* create types and append to tArray until ord is reached *)
383 (* details of these types are to be fixed later *)
384 newT
:= MS
.NewTempType();
385 newT
.SetTypeOrd(indx
); INC(indx
);
386 AppendType(rd
.tArray
, newT
);
393 PROCEDURE (rd
: Reader
) GetTypeFromOrd(): MS
.Type
, NEW;
399 RETURN rd
.TypeOf(ord
);
403 PROCEDURE (rd
: Reader
) GetHeader(modname
: CharOpen
), NEW;
410 marker
:= rd
.ReadInt();
411 IF marker
= RTS
.loInt(magic
) THEN
412 (* normal case, nothing to do *)
413 ELSIF marker
= RTS
.loInt(syMag
) THEN
414 (* should never reach here for foreign module *)
417 Error
.WriteString("File <");
418 Error
.WriteString(GF
.getFullPathName(rd
.file
));
419 Error
.WriteString("> wrong format"); Error
.WriteLn
;
424 IF rd
.sSym
= namSy
THEN
425 IF modname^
# ST
.ToChrOpen(rd
.sAtt
)^
THEN
426 Error
.WriteString("Wrong name in symbol file. Expected <");
427 Error
.WriteString(modname
); Error
.WriteString(">, found <");
428 Error
.WriteString(rd
.sAtt
); Error
.WriteString(">"); Error
.WriteLn
;
433 RTS
.Throw("Bad symfile header");
435 IF rd
.sSym
= strSy
THEN (* optional name *)
436 (* non-GPCP module *)
437 scopeNm
:= ST
.ToChrOpen(rd
.sAtt
);
438 idx1
:= ST
.StrChr(scopeNm
, '
['
); idx2
:= ST
.StrChr(scopeNm
, '
]'
);
439 str
:= ST
.SubStr(scopeNm
,idx1
+1, idx2
-1);
440 rd
.fasb
:= MS
.GetAssemblyByName(ST
.StrSubChr(str
,'
.'
,'_'
));
441 ASSERT(rd
.fasb
# NIL);
442 str
:= ST
.SubStr(scopeNm
, idx2
+1, LEN(scopeNm
)-1);
443 rd
.fns
:= rd
.fasb
.GetNamespace(str
);
444 ASSERT(rd
.fns
# NIL);
447 IF (rd
.sSym
= falSy
) OR (rd
.sSym
= truSy
) THEN
450 RTS
.Throw("Bad explicit name");
454 rd
.fasb
:= MS
.GetAssemblyByName(modname
);
455 ASSERT(rd
.fasb
# NIL);
456 rd
.fns
:= rd
.fasb
.GetNamespace(modname
);
457 ASSERT(rd
.fns
# NIL);
462 PROCEDURE (rd
: Reader
) GetVersionName(), NEW;
466 token
: MS
.PublicKeyToken
;
468 (* get the assembly version *)
469 ASSERT(rd
.sSym
= numSy
); NEW(version
);
470 version
[MS
.Major
] := RTS
.loShort(RTS
.hiInt(rd
.lAtt
));
471 version
[MS
.Minor
] := RTS
.loShort(RTS
.loInt(rd
.lAtt
));
473 version
[MS
.Build
] := RTS
.loShort(RTS
.hiInt(rd
.lAtt
));
474 version
[MS
.Revis
] := RTS
.loShort(RTS
.loInt(rd
.lAtt
));
475 rd
.fasb
.SetVersion(version
);
476 (* get the assembly public key token *)
477 rd
.sSym
:= rd
.Read();
478 ASSERT(rd
.sSym
= numSy
); NEW(token
);
480 token
[i
] := RTS
.loByte(RTS
.loShort(rd
.Read()));
482 rd
.fasb
.SetPublicKeyToken(token
);
483 (* get next symbol *)
488 PROCEDURE (rd
: Reader
)GetLiteral(): MS
.Literal
, NEW;
494 lit
:= MS
.MakeBoolLiteral(TRUE
);
496 lit
:= MS
.MakeBoolLiteral(FALSE
);
498 lit
:= MS
.MakeLIntLiteral(rd
.lAtt
);
500 lit
:= MS
.MakeCharLiteral(rd
.cAtt
);
502 lit
:= MS
.MakeRealLiteral(rd
.rAtt
);
504 lit
:= MS
.MakeSetLiteral(BITS(rd
.iAtt
));
506 lit
:= MS
.MakeStrLiteral(ST
.ToChrOpen(rd
.sAtt
)); (* implicit rd.sAtt^ *)
510 rd
.GetSym(); (* read past value *)
515 PROCEDURE (rd
: Reader
) Import
, NEW;
528 mname
:= ST
.ToChrOpen(rd
.sAtt
);
529 IF rd
.sSym
= strSy
THEN
530 (* non-GPCP module *)
531 scopeNm
:= ST
.ToChrOpen(rd
.sAtt
);
532 idx1
:= ST
.StrChr(scopeNm
, '
['
); idx2
:= ST
.StrChr(scopeNm
, '
]'
);
533 asbfile
:= ST
.SubStr(scopeNm
,idx1
+1, idx2
-1);
534 nsname
:= ST
.SubStr(scopeNm
, idx2
+1, LEN(scopeNm
)-1);
537 (* possible GPCP module *)
539 IF mname
[len
-2] = '_'
THEN mname
:= ST
.SubStr(mname
, 0, len
-3); END;
541 nsname
:= mname
; (* or it can be assigned as MS.NULLSPACE *)
543 (* need to get the assembly real name here *)
544 asbname
:= MP
.GetAssemblyRealName(asbfile
);
545 asb
:= MS
.InsertAssembly(asbname
, asbfile
);
546 ns
:= asb
.InsertNamespace(nsname
);
547 AppendScope(rd
.sArray
, ns
);
552 PROCEDURE (rd
: Reader
) ParseType
, NEW;
557 typ
:= MS
.NewTempType(); (* this is a temporay type, not the final type *)
558 typ
.SetName(ST
.ToChrOpen(rd
.sAtt
));
559 typ
.SetFullName(ST
.StrCat(ST
.StrCatChr(rd
.fns
.GetName(),'
.'
),typ
.GetName()));
560 typ
.SetVisibility(rd
.iAtt
);
562 IF ord
>= tOffset
THEN
563 ASSERT(rd
.tNxt
= ord
);
565 AppendType(rd
.tArray
, typ
); INC(rd
.tNxt
);
566 typ
.SetNamespace(rd
.fns
);
568 (* primitive types *)
574 PROCEDURE (rd
: Reader
) GetFormalTypes(): MS
.FormalList
, NEW;
576 // FormalType = [retSy TypeOrd] frmSy {parSy byte TypeOrd} endFm.
577 // -- optional phrase is return type for proper procedures
595 head
:= NIL; last
:= NIL; count
:= 0; ftype
:= NIL; NEW(str
,3); unresolved
:= 0;
597 WHILE rd
.sSym
= parSy
DO
599 ftype
:= rd
.GetTypeFromOrd();
600 RTS
.IntToStr(count
, str
);
601 WITH ftype
: MS
.NamedType
DO
602 fml
:= MS
.MakeFormal(ST
.StrCat(ST
.ToChrOpen(FNAME
),str
), ftype
, fmode
);
603 | ftype
: MS
.TempType
DO
604 fml
:= MS
.MakeFormal(ST
.StrCat(ST
.ToChrOpen(FNAME
),str
), MS
.dmyTyp
, fmode
);
605 (* collect reference if TempType/NamedType *)
606 ftype
.AddReferenceFormal(fml
);
609 fml
:= MS
.MakeFormal(ST
.StrCat(ST
.ToChrOpen(FNAME
),str
), ftype
, fmode
);
612 (* add the formal to a temporary formals linkedlist *)
613 NEW(temp
); temp
.nxt
:= NIL; temp
.fml
:= fml
;
614 IF last
# NIL THEN last
.nxt
:= temp
; last
:= temp
; ELSE last
:= temp
; head
:= temp
; END;
619 (* now I know how many formals for the method *)
620 rslt
:= MS
.CreateFormalList(count
);
621 temp
:= head
; pos
:= 0;
623 rslt
.AddFormal(temp
.fml
, pos
);
624 temp
:= temp
.nxt
; INC(pos
);
626 rslt
.ostd
:= unresolved
;
631 PROCEDURE FixProcTypes(rec
: MS
.RecordType
; newM
: MS
.Method
; fl
: MS
.FormalList
; rtype
: MS
.Type
);
635 IF MS
.WithoutMethodNameMangling() THEN
637 WITH newF
: MS
.Function
DO
638 WITH rtype
: MS
.TempType
DO
639 (* not a concrete return type *)
640 WITH rtype
: MS
.NamedType
DO
641 (* return type name is resolved *)
643 (* no unresolved formal types names *)
644 newM
.FixSigCode(); (* fix the sigcode of newM *)
645 newM
:= rec
.AddMethod(newM
);
647 (* need to AddMethod after formal type names resolved *)
650 (* return type name is unresolved *)
652 (* need to AddMethod after return type name and formal type names resolved *)
655 (* collect reference if TempType/NamedType *)
656 rtype
.AddReferenceFunction(newF
);
658 (* concrete return type ==> type name is solved *)
660 (* no unresolved formal types names *)
661 newM
.FixSigCode(); (* fix the sigcode of newM *)
662 newM
:= rec
.AddMethod(newM
);
664 (* need to AddMethod after formal type names resolved *)
670 (* no unresolved formal types names *)
671 newM
.FixSigCode(); (* fix the sigcode of newM *)
672 newM
:= rec
.AddMethod(newM
);
674 (* need to AddMethod after formal type names resolved *)
678 newM
.FixSigCode(); (* fix the sigcode of newM *)
679 newM
:= rec
.AddMethod(newM
);
680 WITH newM
: MS
.Function
DO
681 WITH rtype
: MS
.TempType
DO
682 (* collect reference if TempType/NamedType *)
683 rtype
.AddReferenceFunction(newM
);
692 PROCEDURE (rd
: Reader
) ParseMethod(rec
: MS
.RecordType
), NEW;
706 mname
:= ST
.ToChrOpen(rd
.sAtt
);
708 (* byte1 is the method attributes *)
709 mAtt
:= BITS(rd
.Read());
710 (* byte2 is param form of receiver *)
712 (* next 1 or 2 bytes are rcv-type *)
713 rectyp
:= rd
.TypeOf(rd
.ReadOrd());
717 IF ~MS
.WithoutMethodNameMangling() THEN
718 IF rd
.sSym
= strSy
THEN
719 (* optional invoking method name *)
721 mname
:= ST
.ToChrOpen(rd
.sAtt
);
727 IF rd
.sSym
= retSy
THEN
728 rtype
:= rd
.TypeOf(rd
.iAtt
);
731 fl
:= rd
.GetFormalTypes();
733 newM
:= rec
.MakeMethod(mname
, MS
.Mnonstatic
, rtype
, fl
);
734 IF (rectyp
# NIL) & (rectyp
# rec
) THEN newM
.SetDeclaringType(rectyp
); END;
736 IF MS
.WithoutMethodNameMangling() THEN
738 IF ovlname
# NIL THEN
739 newM
.SetOverload(ovlname
); (* fix the sigcode of newM *)
744 newM
.SetVisibility(vMod
);
745 newM
.InclAttributes(mAtt
);
746 FixProcTypes(rec
, newM
, fl
, rtype
);
750 PROCEDURE (rd
: Reader
) ParseProcedure(rec
: MS
.RecordType
), NEW;
766 pname
:= ST
.ToChrOpen(rd
.sAtt
);
770 ivkname
:= NIL; ovlname
:= NIL; isCtor
:= FALSE
;
772 IF rd
.sSym
= strSy
THEN
773 (* optional string of invoke name if overloaded method OR Constructor *)
774 ivkname
:= ST
.ToChrOpen(rd
.sAtt
);
777 IF rd
.sSym
= truSy
THEN
778 (* optional truSy shows that procedure is a constructor *)
780 IF LEN(pname
) > LEN(MS
.replCtor
) THEN
781 (* overload constructor name is in the form of "init_..." *)
783 idx
:= ST
.StrChr(ovlname
,'_'
);
784 IF idx
# ST
.NotExist
THEN
785 pname
:= ST
.SubStr(ovlname
, 0, idx
-1);
790 (* constructor is not overloaded *)
794 (* not a constructor *)
801 IF rd
.sSym
= retSy
THEN
802 rtype
:= rd
.TypeOf(rd
.iAtt
);
805 fl
:= rd
.GetFormalTypes();
807 newP
:= rec
.MakeMethod(pname
, MS
.Mstatic
, rtype
, fl
);
809 newP
.SetConstructor();
810 newP
.SetInvokeName(ivkname
);
813 IF MS
.WithoutMethodNameMangling() THEN
815 IF ovlname
# NIL THEN
816 newP
.SetOverload(ovlname
); (* fix the sigcode of newM *)
820 newP
.SetVisibility(vMod
);
821 FixProcTypes(rec
, newP
, fl
, rtype
);
825 PROCEDURE (rd
: Reader
) ParseRecordField(rec
: MS
.RecordType
), NEW;
832 fldname
:= ST
.ToChrOpen(rd
.sAtt
);
834 ftyp
:= rd
.TypeOf(rd
.ReadOrd());
836 WITH ftyp
: MS
.NamedType
DO
837 fld
:= rec(MS
.ValueType
).MakeField(fldname
, ftyp
, FALSE
);
838 | ftyp
: MS
.TempType
DO
839 fld
:= rec(MS
.ValueType
).MakeField(fldname
, MS
.dmyTyp
, FALSE
);
840 (* collect reference if TempType/NamedType *)
841 ftyp
.AddReferenceField(fld
);
843 fld
:= rec(MS
.ValueType
).MakeField(fldname
, ftyp
, FALSE
);
846 fld
.SetVisibility(fvmod
);
847 WITH rec
: MS
.PrimType
DO (* for IntPtr and UIntPtr, otherwise StrucType *)
848 ASSERT(rec
.AddField(fld
, FALSE
));
849 ELSE (* IntfcType should not has data member *)
852 END ParseRecordField
;
855 PROCEDURE (rd
: Reader
) ParseStaticVariable(rec
: MS
.RecordType
), NEW;
856 (* Variable = varSy Name TypeOrd. *)
863 varname
:= ST
.ToChrOpen(rd
.sAtt
);
865 vtyp
:= rd
.TypeOf(rd
.ReadOrd());
867 WITH vtyp
: MS
.NamedType
DO
868 newV
:= rec(MS
.ValueType
).MakeField(varname
, vtyp
, FALSE
);
869 | vtyp
: MS
.TempType
DO
870 newV
:= rec(MS
.ValueType
).MakeField(varname
, MS
.dmyTyp
, FALSE
);
871 (* collect reference if TempType/NamedType *)
872 vtyp
.AddReferenceField(newV
);
874 newV
:= rec(MS
.ValueType
).MakeField(varname
, vtyp
, FALSE
);
877 newV
.SetVisibility(vvmod
);
878 WITH rec
: MS
.PrimType
DO (* for IntPtr and UIntPtr, otherwise StrucType *)
879 ASSERT(rec
.AddField(newV
, TRUE
));
880 ELSE (* IntfcType should not has data member *)
884 END ParseStaticVariable
;
887 PROCEDURE (rd
: Reader
) ParseConstant(rec
: MS
.RecordType
), NEW;
888 (* Constant = conSy Name Literal. *)
889 (* Assert: f.sSym = namSy. *)
898 cname
:= ST
.ToChrOpen(rd
.sAtt
);
901 cvalue
:= rd
.GetLiteral();
903 IF cvalue
IS MS
.BoolLiteral
THEN
905 ELSIF cvalue
IS MS
.LIntLiteral
THEN
907 ELSIF cvalue
IS MS
.CharLiteral
THEN
909 ELSIF cvalue
IS MS
.RealLiteral
THEN
911 ELSIF cvalue
IS MS
.SetLiteral
THEN
913 ELSIF cvalue
IS MS
.StrLiteral
THEN
916 tord
:= MS
.unCertain
;
918 ctyp
:= MS
.baseTypeArray
[tord
];
920 ctyp
:= MS
.MakeDummyPrimitive(tord
);
922 newC
:= rec(MS
.ValueType
).MakeConstant(cname
, ctyp
, cvalue
);
924 newC
.SetVisibility(cvmod
);
925 WITH rec
: MS
.ValueType
DO
926 ASSERT(rec
.AddField(newC
, TRUE
));
927 ELSE (* IntfcType should not has data member *)
934 PROCEDURE (rd
: Reader
) ParsePointerType(old
: MS
.Type
): MS
.Type
, NEW;
937 rslt
: MS
.PointerType
;
944 (* read the target type ordinal *)
945 indx
:= rd
.ReadOrd();
946 WITH old
: MS
.PointerType
DO
949 * Check if there is space in the tArray for this
950 * element, otherwise expand using typeOf().
952 IF indx
- tOffset
>= rd
.tArray
.tide
THEN
953 junk
:= rd
.TypeOf(indx
);
955 rd
.tArray
.a
[indx
-tOffset
] := rslt
.GetTarget();
956 | old
: MS
.TempType
DO
957 ns
:= old
.GetNamespace();
959 (* it is an anonymous pointer to array type *)
961 target
:= rd
.TypeOf(indx
);
962 rslt
:= MS
.MakeAnonymousPointerType(target
);
964 tname
:= old
.GetName();
965 ftname
:= old
.GetFullName();
966 target
:= rd
.TypeOf(indx
);
967 target
.SetNamespace(ns
); (* the the default namespace of the target *)
968 rslt
:= ns
.InsertPointer(tname
,ftname
,target
);
969 rslt
.SetVisibility(old
.GetVisibility());
972 (* changed from TempType to PointerType, so fix all references to the type *)
973 MS
.FixReferences(old
, rslt
);
975 IF target
.GetName() = NIL THEN
976 target
.SetAnonymous();
977 target
.SetVisibility(MS
.Vprivate
);
978 (* collect reference if TempType/NamedType *)
979 target(MS
.TempType
).AddSrcPointerType(rslt
); (* <== should that be for all TempType target?? *)
983 ASSERT(FALSE
); rslt
:= NIL;
987 END ParsePointerType
;
990 PROCEDURE (rd
: Reader
) ParseArrayType(tpTemp
: MS
.Type
): MS
.Type
, NEW;
998 sptr
: MS
.PointerType
;
1002 typOrd
:= rd
.ReadOrd();
1003 elemTp
:= rd
.TypeOf(typOrd
);
1004 ns
:= tpTemp
.GetNamespace();
1006 (* its name (currently "DummyType") can only be fixed after its element type is determined *)
1007 tpTemp
.SetAnonymous();
1008 IF typOrd
< tOffset
THEN
1009 (* element type is primitive, and was already create by TypeOf() calling MakeDummyPrimitive() *)
1010 tname
:= elemTp
.GetName();
1011 tname
:= ST
.StrCat(tname
, MS
.anonArr
); (* append "_arr" *)
1012 ns
:= elemTp
.GetNamespace(); (* []SYSTEM - for dummy primitives *)
1013 ftname
:= ST
.StrCatChr(ns
.GetName(), '
.'
);
1014 ftname
:= ST
.StrCat(ftname
, tname
);
1016 ns
:= elemTp
.GetNamespace();
1018 (* the anonymous array element is already known *)
1019 tname
:= elemTp
.GetName();
1020 tname
:= ST
.StrCat(tname
, MS
.anonArr
); (* append "_arr" *)
1021 ftname
:= ST
.StrCatChr(ns
.GetName(), '
.'
);
1022 ftname
:= ST
.StrCat(ftname
, tname
);
1024 (* cannot insert this type as its element type is still unknown, and so is its namespace ??? *)
1025 tname
:= ST
.NullString
;
1030 IF ~tpTemp
.IsAnonymous() THEN
1031 tname
:= tpTemp
.GetName();
1032 ftname
:= tpTemp
.GetFullName();
1034 (* if array is anonymous and has namespace,
1035 then either its element type has been parsed (ARRAY OF ParsedElement),
1036 or it has a src pointer type (Arr1AnonymousArray = POINTER TO ARRAY OF something) *)
1037 tname
:= elemTp
.GetName();
1039 tname
:= ST
.StrCat(tname
, MS
.anonArr
); (* append "_arr" *)
1041 sptr
:= tpTemp(MS
.TempType
).GetNonAnonymousPTCrossRef();
1042 sptrname
:= sptr
.GetName();
1043 tname
:= ST
.SubStr(sptrname
, 4, LEN(sptrname
)-1); (* get rid of "Arr1" *)
1044 tname
:= ST
.StrCat(tname
, MS
.anonArr
); (* append "_arr" *)
1046 ftname
:= ST
.StrCatChr(ns
.GetName(), '
.'
);
1047 ftname
:= ST
.StrCat(ftname
, tname
);
1051 IF rd
.sSym
= bytSy
THEN
1054 ELSIF rd
.sSym
= numSy
THEN
1055 length
:= SHORT(rd
.lAtt
);
1062 rslt
:= ns
.InsertArray(tname
, ftname
, 1, length
, elemTp
);
1063 rslt
.SetVisibility(tpTemp
.GetVisibility());
1065 (* changed from TempType to ArrayType, so fix all references to the type *)
1066 MS
.FixReferences(tpTemp
, rslt
);
1068 IF tpTemp
.IsAnonymous() THEN
1069 rslt
.SetAnonymous();
1071 rslt
.NotAnonymous();
1074 (* add this to defer anonymous array insertion list*)
1075 tpTemp(MS
.TempType
).SetDimension(1);
1076 tpTemp(MS
.TempType
).SetLength(length
);
1077 elemTp(MS
.TempType
).AddAnonymousArrayType(tpTemp(MS
.TempType
));
1086 PROCEDURE (rd
: Reader
) ParseRecordType(old
: MS
.Type
; typIdx
: INTEGER): MS
.RecordType
, NEW;
1087 (* Assert: at entry the current symbol is recSy. *)
1088 (* Record = TypeHeader recSy recAtt [truSy | falSy | <others>] *)
1089 (* [basSy TypeOrd] [iFcSy {basSy TypeOrd}] *)
1090 (* {Name TypeOrd} {Method} {Statics} endRc. *)
1092 rslt
: MS
.RecordType
;
1098 isValueType
: BOOLEAN; (* is ValueType *)
1099 hasNarg
: BOOLEAN; (* has noarg constructor ( can use NEW() ) *)
1105 sptr
: MS
.PointerType
;
1108 tord
: INTEGER; (* temporary type storage *)
1109 ttyp
: MS
.Type
; (* temporary type storage *)
1113 WITH old
: MS
.RecordType
DO
1115 recAtt
:= rd
.Read(); (* record attribute *) (* <==== *)
1116 rd
.GetSym(); (* falSy *)
1117 rd
.GetSym(); (* optional basSy *)
1118 IF rd
.sSym
= basSy
THEN rd
.GetSym() END;
1119 | old
: MS
.TempType
DO
1121 ns
:= old
.GetNamespace();
1122 IF ~old
.IsAnonymous() THEN
1123 tname
:= old
.GetName();
1124 ftname
:= old
.GetFullName();
1126 (* if record is anonymous, it has only one src pointer type *)
1127 sptr
:= old(MS
.TempType
).GetFirstPTCrossRef();
1128 tname
:= ST
.StrCat(sptr
.GetName(), MS
.anonRec
);
1129 ftname
:= ST
.StrCatChr(ns
.GetName(), '
.'
);
1130 ftname
:= ST
.StrCat(ftname
, tname
);
1133 recAtt
:= rd
.Read(); (* <==== *)
1134 (* check for ValueType *)
1135 IF recAtt
>= valTp
THEN
1136 isValueType
:= TRUE
; recAtt
:= recAtt
MOD valTp
;
1138 isValueType
:= FALSE
;
1141 (* check for no NOARG constructor *)
1142 IF recAtt
>= nnarg
THEN
1143 hasNarg
:= FALSE
; recAtt
:= recAtt
MOD nnarg
;
1148 (* Record default to Struct, change to Class if found to be ClassType later (when it has event?) *)
1150 IF recAtt
= iFace
THEN tt
:= MS
.Interface
; END;
1153 IF rd
.sSym
= falSy
THEN
1154 ELSIF rd
.sSym
= truSy
THEN
1157 rslt
:= ns
.InsertRecord(tname
, ftname
, tt
);
1158 rslt
.SetVisibility(old
.GetVisibility());
1160 IF isValueType
THEN rslt
.InclAttributes(MS
.RvalTp
); END;
1161 IF hasNarg
THEN rslt
.SetHasNoArgConstructor(); END;
1164 abstr
: rslt
.InclAttributes(MS
.Rabstr
);
1165 | limit
: (* foreign has no LIMITED attribute *)
1166 | extns
: rslt
.InclAttributes(MS
.Rextns
);
1172 IF rd
.sSym
= basSy
THEN
1173 base
:= rd
.TypeOf(rd
.iAtt
);
1174 WITH base
: MS
.NamedType
DO
1175 rslt
.SetBaseType(base
);
1176 | base
: MS
.TempType
DO
1177 (* base is a temp type *)
1178 (* collect reference if TempType/NamedType *)
1179 base(MS
.TempType
).AddDeriveRecordType(rslt
);
1181 (* base has already been parsed *)
1182 rslt
.SetBaseType(base
);
1187 IF rd
.sSym
= iFcSy
THEN
1189 WHILE rd
.sSym
= basSy
DO
1191 itfc
:= rd
.TypeOf(rd
.iAtt
);
1192 WITH itfc
: MS
.NamedType
DO
1193 (* add to interface list of rslt *)
1194 rslt
.AddInterface(itfc
);
1195 | itfc
: MS
.TempType
DO
1196 (* itfc is a temp type *)
1197 (* collect reference *)
1198 itfc(MS
.TempType
).AddImplRecordType(rslt
);
1200 (* itfc has already been parsed *)
1201 (* add to interface list of rslt *)
1202 rslt
.AddInterface(itfc
);
1208 (* changed from TempType to RecordType, so fix all references to the type *)
1209 MS
.FixReferences(old
, rslt
);
1210 (* need to be here as its methods, fields, etc. may reference to this new type *)
1211 rd
.tArray
.a
[typIdx
] := rslt
;
1213 ASSERT(FALSE
); rslt
:= NIL;
1216 WHILE rd
.sSym
= namSy
DO
1217 (* check for record fields *)
1218 rd
.ParseRecordField(rslt
);
1220 (* insert the field to the record's field list *)
1223 WHILE (rd
.sSym
= mthSy
) OR (rd
.sSym
= prcSy
) OR
1224 (rd
.sSym
= varSy
) OR (rd
.sSym
= conSy
) DO
1225 oldS
:= rd
.sSym
; rd
.GetSym();
1226 IF oldS
= mthSy
THEN
1227 rd
.ParseMethod(rslt
);
1228 ELSIF oldS
= prcSy
THEN
1229 rd
.ParseProcedure(rslt
);
1230 ELSIF oldS
= varSy
THEN
1231 rd
.ParseStaticVariable(rslt
);
1232 ELSIF oldS
= conSy
THEN
1233 rd
.ParseConstant(rslt
);
1240 END ParseRecordType
;
1243 PROCEDURE (rd
: Reader
) ParseEnumType(tpTemp
: MS
.Type
): MS
.Type
, NEW;
1252 ns
:= tpTemp
.GetNamespace();
1253 tname
:= tpTemp
.GetName();
1254 ftname
:= tpTemp
.GetFullName();
1255 rslt
:= ns
.InsertRecord(tname
, ftname
, MS
.Enum
)(MS
.EnumType
);
1256 rslt
.SetVisibility(tpTemp
.GetVisibility());
1258 (* changed from TempType to EnumType, so fix all references to the type *)
1259 MS
.FixReferences(tpTemp
, rslt
);
1262 WHILE rd
.sSym
= conSy
DO
1264 rd
.ParseConstant(rslt
);
1271 PROCEDURE (rd
: Reader
) ParseDelegType(old
: MS
.Type
; isMul
: BOOLEAN): MS
.Type
, NEW;
1273 rslt
: MS
.PointerType
;
1279 target
: MS
.RecordType
;
1285 (* create the pointer *)
1286 WITH old
: MS
.PointerType
DO
1288 | old
: MS
.TempType
DO
1289 ns
:= old
.GetNamespace();
1292 tname
:= old
.GetName();
1293 ftname
:= old
.GetFullName();
1296 ttname
:= ST
.StrCat(tname
, MS
.anonRec
);
1297 tftname
:= ST
.StrCatChr(ns
.GetName(), '
.'
);
1298 tftname
:= ST
.StrCat(tftname
, ttname
);
1300 (* create the target record *)
1301 target
:= ns
.InsertRecord(ttname
, tftname
, MS
.Delegate
);
1302 target
.SetNamespace(ns
); (* the the default namespace of the target *)
1303 target
.SetAnonymous();
1304 IF isMul
THEN target
.SetMulticast() END;
1306 (* target visibility *)
1307 target
.SetVisibility(MS
.Vprivate
);
1308 (* Delegate is not value type *)
1309 (* Delegate has no noarg constructor *)
1310 (* Delegate is neither abstract, nor extensible *)
1311 (* lost information on base type of Delegate *)
1312 (* lost information on interface implemented by Delegate *)
1314 rslt
:= ns
.InsertPointer(tname
,ftname
,target
);
1315 rslt
.SetVisibility(old
.GetVisibility());
1317 (* changed from TempType to PointerType, so fix all references to the type *)
1318 MS
.FixReferences(old
, rslt
);
1320 (* the "Invoke" method of delegate *)
1324 IF rd
.sSym
= retSy
THEN
1325 rtype
:= rd
.TypeOf(rd
.iAtt
);
1329 fl
:= rd
.GetFormalTypes();
1331 newM
:= target
.MakeMethod(ST
.ToChrOpen("Invoke"), MS
.Mnonstatic
, rtype
, fl
);
1332 newM
.SetVisibility(MS
.Vpublic
); (* "Invoke" method has Public visiblilty *)
1334 (* "Invoke" method has final {} attribute (or should it has NEW attribute) *)
1335 (* newM.InclAttributes(MS.Mnew); *)
1337 FixProcTypes(target
, newM
, fl
, rtype
);
1339 ASSERT(FALSE
); rslt
:= NIL;
1346 PROCEDURE (rd
: Reader
) ParseTypeList
*(), NEW;
1347 (* TypeList = start { Array | Record | Pointer *)
1348 (* | ProcType } close. *)
1349 (* TypeHeader = tDefS Ord [fromS Ord Name]. *)
1355 impMod
: MS
.Namespace
;
1359 WHILE rd
.sSym
= tDefS
DO
1360 (* Do type header *)
1362 typIdx
:= typOrd
- tOffset
;
1363 tpTemp
:= rd
.tArray
.a
[typIdx
];
1366 (* The fromS symbol appears if the type is imported *)
1367 IF rd
.sSym
= fromS
THEN
1369 impMod
:= rd
.sArray
.a
[modOrd
-1];
1371 (* With the strict ordering of the imports,
1372 * it may be unnecessary to create this object
1373 * in case the other module has been fully read
1375 * It is also possible that the type has
1376 * been imported already, but just as an opaque.
1378 tpTemp
.SetNamespace(impMod
);
1382 IF tpTemp
.GetName() = NIL THEN
1383 tpTemp
.SetName(ST
.ToChrOpen(rd
.sAtt
));
1386 tpTemp
.SetFullName(ST
.StrCat(ST
.StrCatChr(impMod
.GetName(),'
.'
), tpTemp
.GetName()));
1392 tpDesc
:= rd
.ParseArrayType(tpTemp
);
1393 rd
.tArray
.a
[typIdx
] := tpDesc
;
1395 tpDesc
:= rd
.ParseRecordType(tpTemp
, typIdx
);
1396 rd
.tArray
.a
[typIdx
] := tpDesc
;
1398 tpDesc
:= rd
.ParsePointerType(tpTemp
);
1399 rd
.tArray
.a
[typIdx
] := tpDesc
;
1401 tpDesc
:= rd
.ParseDelegType(tpTemp
, TRUE
);
1402 rd
.tArray
.a
[typIdx
] := tpDesc
;
1404 tpDesc
:= rd
.ParseDelegType(tpTemp
, FALSE
);
1405 rd
.tArray
.a
[typIdx
] := tpDesc
;
1407 tpDesc
:= rd
.ParseEnumType(tpTemp
);
1408 rd
.tArray
.a
[typIdx
] := tpDesc
;
1410 (* NamedTypes come here *)
1411 IF impMod
= NIL THEN impMod
:= rd
.fns
; END;
1412 (* the outcome could be a PointerType, ArrayType or RecordType if it already exist *)
1413 tpDesc
:= impMod
.InsertNamedType(tpTemp
.GetName(), tpTemp
.GetFullName());
1414 rd
.tArray
.a
[typIdx
] := tpDesc
;
1415 (* changed from TempType to NamedType, so fix all references to the type *)
1416 MS
.FixReferences(tpTemp
, tpDesc
);
1423 PROCEDURE (rd
: Reader
) InsertMainClass(): MS
.PointerType
, NEW;
1425 tname
: ST
.CharOpen
;
1426 tgtname
: ST
.CharOpen
;
1427 target
: MS
.RecordType
;
1428 rslt
: MS
.PointerType
;
1433 ASSERT(ST
.StrCmp(rd
.fasb
.GetName(), rd
.fns
.GetName()) = ST
.Equal
);
1434 tname
:= rd
.fns
.GetName();
1435 tgtname
:= ST
.StrCat(tname
, MS
.anonRec
);
1436 target
:= rd
.fns
.InsertRecord(tgtname
, tgtname
, MS
.Struct
);
1437 target
.SetVisibility(MS
.Vpublic
);
1438 target
.SetHasNoArgConstructor();
1439 base
:= MS
.GetTypeByName(ST
.ToChrOpen("mscorlib"),ST
.ToChrOpen("System"),ST
.ToChrOpen("Object"));
1440 ASSERT(base
# NIL); (* mscorlib_System.Object should always exist *)
1441 target
.SetBaseType(base
);
1442 rslt
:= rd
.fns
.InsertPointer(tname
,tname
,target
);
1443 rslt
.SetVisibility(MS
.Vpublic
);
1445 END InsertMainClass
;
1448 PROCEDURE ParseSymbolFile
*(symfile
: GF
.FILE
; modname
: CharOpen
);
1452 class
: MS
.PointerType
;
1456 rd
:= NewReader(symfile
);
1457 rd
.GetHeader(modname
);
1458 IF rd
.sSym
= numSy
THEN rd
.GetVersionName(); END; (* optional strong name info. *)
1464 | impSy
: rd
.Import();
1465 | typSy
: rd
.ParseType();
1466 | conSy
: (* a global variable belongs to an GPCP module, e.g. ["[GPFiles]GPFiles"] *)
1468 class
:= rd
.InsertMainClass();
1469 rec
:= class
.GetTarget();
1471 WITH rec
: MS
.RecordType
DO
1472 rd
.ParseConstant(rec
);
1476 | prcSy
: (* a global variable belongs to an GPCP module, e.g. ["[GPFiles]GPFiles"] *)
1478 class
:= rd
.InsertMainClass();
1479 rec
:= class
.GetTarget();
1481 WITH rec
: MS
.RecordType
DO
1482 rd
.ParseProcedure(rec
);
1486 | varSy
: (* a global variable belongs to an GPCP module, e.g. ["[GPFiles]GPFiles"] *)
1488 class
:= rd
.InsertMainClass();
1489 rec
:= class
.GetTarget();
1491 WITH rec
: MS
.RecordType
DO
1492 rd
.ParseStaticVariable(rec
);
1497 RTS
.Throw("Bad object");
1501 IF rd
.sSym
# keySy
THEN RTS
.Throw("Missing keySy"); END;
1502 END ParseSymbolFile
;