123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010 |
- {
- This file is part of the Free Component Library
- Pascal source parser
- Copyright (c) 2000-2005 by
- Areca Systems GmbH / Sebastian Guenther, [email protected]
- See the file COPYING.FPC, included in this distribution,
- for details about the copyright.
- This program is distributed in the hope that it will be useful,
- but WITHOUT ANY WARRANTY; without even the implied warranty of
- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
- **********************************************************************}
- unit PParser;
- interface
- uses SysUtils, PasTree, PScanner;
- resourcestring
- SErrNoSourceGiven = 'No source file specified';
- SErrMultipleSourceFiles = 'Please specify only one source file';
- SParserError = 'Error';
- SParserErrorAtToken = '%s at token "%s"';
- SParserUngetTokenError = 'Internal error: Cannot unget more tokens, history buffer is full';
- SParserExpectTokenError = 'Expected "%s"';
- SParserExpectedCommaRBracket = 'Expected "," or ")"';
- SParserExpectedCommaSemicolon = 'Expected "," or ";"';
- SParserExpectedCommaColon = 'Expected "," or ":"';
- SParserExpectedLBracketColon = 'Expected "(" or ":"';
- SParserExpectedLBracketSemicolon = 'Expected "(" or ";"';
- SParserExpectedColonSemicolon = 'Expected ":" or ";"';
- SParserExpectedSemiColonEnd = 'Expected ";" or "End"';
- SParserExpectedConstVarID = 'Expected "const", "var" or identifier';
- SParserSyntaxError = 'Syntax error';
- SParserTypeSyntaxError = 'Syntax error in type';
- SParserArrayTypeSyntaxError = 'Syntax error in array type';
- SParserInterfaceTokenError = 'Invalid token in interface section of unit';
- SParserInvalidTypeDef = 'Invalid type definition';
- type
- TPasTreeContainer = class
- protected
- FPackage: TPasPackage;
- public
- function CreateElement(AClass: TPTreeElement; const AName: String;
- AParent: TPasElement; const ASourceFilename: String;
- ASourceLinenumber: Integer): TPasElement;
- function CreateElement(AClass: TPTreeElement; const AName: String;
- AParent: TPasElement; AVisibility: TPasMemberVisibility;
- const ASourceFilename: String; ASourceLinenumber: Integer): TPasElement;
- virtual; abstract;
- function CreateFunctionType(const AName, AResultName: String; AParent: TPasElement;
- UseParentAsResultParent: Boolean; const ASourceFilename: String;
- ASourceLinenumber: Integer): TPasFunctionType;
- function FindElement(const AName: String): TPasElement; virtual; abstract;
- function FindModule(const AName: String): TPasModule; virtual;
- property Package: TPasPackage read FPackage;
- end;
- EParserError = class(Exception)
- private
- FFilename: String;
- FRow, FColumn: Integer;
- public
- constructor Create(const AReason, AFilename: String;
- ARow, AColumn: Integer);
- property Filename: String read FFilename;
- property Row: Integer read FRow;
- property Column: Integer read FColumn;
- end;
- function ParseSource(AEngine: TPasTreeContainer;
- const FPCCommandLine, OSTarget, CPUTarget: String): TPasModule;
- implementation
- uses Classes;
- type
- TDeclType = (declNone, declConst, declResourcestring, declType, declVar, declThreadvar);
- TProcType = (ptProcedure, ptFunction, ptOperator);
- TPasParser = class
- private
- FFileResolver: TFileResolver;
- FScanner: TPascalScanner;
- FEngine: TPasTreeContainer;
- FCurToken: TToken;
- FCurTokenString: String;
- // UngetToken support:
- FTokenBuffer: array[0..1] of TToken;
- FTokenStringBuffer: array[0..1] of String;
- FTokenBufferIndex, FTokenBufferSize: Integer;
- procedure ParseExc(const Msg: String);
- protected
- function CreateElement(AClass: TPTreeElement; const AName: String;
- AParent: TPasElement): TPasElement;
- function CreateElement(AClass: TPTreeElement; const AName: String;
- AParent: TPasElement; AVisibility: TPasMemberVisibility): TPasElement;
- public
- Options : set of TPOptions;
- constructor Create(AScanner: TPascalScanner; AFileResolver: TFileResolver;
- AEngine: TPasTreeContainer);
- function CurTokenName: String;
- function CurTokenText: String;
- procedure NextToken;
- procedure UngetToken;
- procedure ExpectToken(tk: TToken);
- function ExpectIdentifier: String;
- function ParseType(Parent: TPasElement; Prefix : String): TPasType;
- function ParseType(Parent: TPasElement): TPasType;
- function ParseComplexType: TPasType;
- procedure ParseArrayType(Element: TPasArrayType);
- function ParseExpression: String;
- procedure AddProcOrFunction(ASection: TPasSection; AProc: TPasProcedure);
- function CheckIfOverloaded(AOwner: TPasClassType;
- const AName: String): TPasElement;
- procedure ParseMain(var Module: TPasModule);
- procedure ParseUnit(var Module: TPasModule);
- procedure ParseUsesList(ASection: TPasSection);
- function ParseConstDecl(Parent: TPasElement): TPasConst;
- function ParseResourcestringDecl(Parent: TPasElement): TPasResString;
- function ParseTypeDecl(Parent: TPasElement): TPasType;
- procedure ParseInlineVarDecl(Parent: TPasElement; VarList: TList);
- procedure ParseInlineVarDecl(Parent: TPasElement; VarList: TList;
- AVisibility : TPasMemberVisibility; ClosingBrace: Boolean);
- procedure ParseVarDecl(Parent: TPasElement; List: TList);
- procedure ParseArgList(Parent: TPasElement; Args: TList; EndToken: TToken);
- procedure ParseProcedureOrFunctionHeader(Parent: TPasElement;
- Element: TPasProcedureType; ProcType: TProcType; OfObjectPossible: Boolean);
- function ParseProcedureOrFunctionDecl(Parent: TPasElement;
- ProcType: TProcType): TPasProcedure;
- procedure ParseRecordDecl(Parent: TPasRecordType; IsNested: Boolean); // !!!: Optimize this. We have 3x the same wrapper code around it.
- function ParseClassDecl(Parent: TPasElement; const AClassName: String;
- AObjKind: TPasObjKind): TPasType;
- procedure ParseProperty(Element:TPasElement);
- property FileResolver: TFileResolver read FFileResolver;
- property Scanner: TPascalScanner read FScanner;
- property Engine: TPasTreeContainer read FEngine;
- property CurToken: TToken read FCurToken;
- property CurTokenString: String read FCurTokenString;
- end;
- function TPasTreeContainer.CreateElement(AClass: TPTreeElement;
- const AName: String; AParent: TPasElement; const ASourceFilename: String;
- ASourceLinenumber: Integer): TPasElement;
- begin
- Result := CreateElement(AClass, AName, AParent, visDefault, ASourceFilename,
- ASourceLinenumber);
- end;
- function TPasTreeContainer.CreateFunctionType(const AName, AResultName: String;
- AParent: TPasElement; UseParentAsResultParent: Boolean;
- const ASourceFilename: String; ASourceLinenumber: Integer): TPasFunctionType;
- var
- ResultParent: TPasElement;
- begin
- Result := TPasFunctionType(CreateElement(TPasFunctionType, AName, AParent,
- ASourceFilename, ASourceLinenumber));
- if UseParentAsResultParent then
- ResultParent := AParent
- else
- ResultParent := Result;
- TPasFunctionType(Result).ResultEl :=
- TPasResultElement(CreateElement(TPasResultElement, AResultName, ResultParent,
- ASourceFilename, ASourceLinenumber));
- end;
- function TPasTreeContainer.FindModule(const AName: String): TPasModule;
- begin
- Result := nil;
- end;
- constructor EParserError.Create(const AReason, AFilename: String;
- ARow, AColumn: Integer);
- begin
- inherited Create(AReason);
- FFilename := AFilename;
- FRow := ARow;
- FColumn := AColumn;
- end;
- procedure TPasParser.ParseExc(const Msg: String);
- begin
- raise EParserError.Create(Format(SParserErrorAtToken, [Msg, CurTokenName]),
- Scanner.CurFilename, Scanner.CurRow, Scanner.CurColumn);
- end;
- constructor TPasParser.Create(AScanner: TPascalScanner;
- AFileResolver: TFileResolver; AEngine: TPasTreeContainer);
- begin
- inherited Create;
- FScanner := AScanner;
- FFileResolver := AFileResolver;
- FEngine := AEngine;
- end;
- function TPasParser.CurTokenName: String;
- begin
- if CurToken = tkIdentifier then
- Result := 'Identifier ' + Scanner.CurTokenString
- else
- Result := TokenInfos[CurToken];
- end;
- function TPasParser.CurTokenText: String;
- begin
- case CurToken of
- tkIdentifier, tkString, tkNumber, tkChar:
- Result := Scanner.CurTokenString;
- else
- Result := TokenInfos[CurToken];
- end;
- end;
- procedure TPasParser.NextToken;
- begin
- if FTokenBufferIndex < FTokenBufferSize then
- begin
- // Get token from buffer
- FCurToken := FTokenBuffer[FTokenBufferIndex];
- FCurTokenString := FTokenStringBuffer[FTokenBufferIndex];
- Inc(FTokenBufferIndex);
- end else
- begin
- { We have to fetch a new token. But first check, wether there is space left
- in the token buffer.}
- if FTokenBufferSize = 2 then
- begin
- FTokenBuffer[0] := FTokenBuffer[1];
- FTokenStringBuffer[0] := FTokenStringBuffer[1];
- Dec(FTokenBufferSize);
- Dec(FTokenBufferIndex);
- end;
- // Fetch new token
- try
- repeat
- FCurToken := Scanner.FetchToken;
- until not (FCurToken in [tkWhitespace, tkComment]);
- except
- on e: EScannerError do
- raise EParserError.Create(e.Message,
- Scanner.CurFilename, Scanner.CurRow, Scanner.CurColumn);
- end;
- FCurTokenString := Scanner.CurTokenString;
- FTokenBuffer[FTokenBufferSize] := FCurToken;
- FTokenStringBuffer[FTokenBufferSize] := FCurTokenString;
- Inc(FTokenBufferSize);
- Inc(FTokenBufferIndex);
- end;
- end;
- procedure TPasParser.UngetToken;
- begin
- if FTokenBufferIndex = 0 then
- ParseExc(SParserUngetTokenError)
- else
- Dec(FTokenBufferIndex);
- end;
- procedure TPasParser.ExpectToken(tk: TToken);
- begin
- NextToken;
- if CurToken <> tk then
- ParseExc(Format(SParserExpectTokenError, [TokenInfos[tk]]));
- end;
- function TPasParser.ExpectIdentifier: String;
- begin
- ExpectToken(tkIdentifier);
- Result := CurTokenString;
- end;
- function TPasParser.ParseType(Parent: TPasElement): TPasType;
- begin
- Result:=ParseType(Parent,'');
- end;
- function TPasParser.ParseType(Parent: TPasElement; Prefix : String): TPasType;
- procedure ParseRange;
- begin
- Result := TPasRangeType(CreateElement(TPasRangeType, '', Parent));
- try
- TPasRangeType(Result).RangeStart := ParseExpression;
- ExpectToken(tkDotDot);
- TPasRangeType(Result).RangeEnd := ParseExpression;
- except
- Result.Free;
- raise;
- end;
- end;
- var
- Name, s: String;
- EnumValue: TPasEnumValue;
- Ref: TPasElement;
- HadPackedModifier : Boolean; // 12/04/04 - Dave - Added
- begin
- Result := nil; // !!!: Remove in the future
- HadPackedModifier := False; { Assume not present }
- NextToken;
- if CurToken = tkPacked then { If PACKED modifier }
- begin { Handle PACKED modifier for all situations }
- NextToken; { Move to next token for rest of parse }
- if CurToken in [tkArray, tkRecord, tkObject, tkClass] then { If allowed }
- HadPackedModifier := True { rememeber for later }
- else { otherwise, syntax error }
- ParseExc(Format(SParserExpectTokenError,['ARRAY, RECORD, OBJECT or CLASS']))
- end;
- case CurToken of
- tkIdentifier:
- begin
- Name := CurTokenString;
- If (Prefix<>'') then
- Name:=Prefix+'.'+Name;
- NextToken;
- if CurToken = tkDot then
- begin
- ExpectIdentifier;
- Name := Name+'.'+CurTokenString;
- end else
- UngetToken;
- Ref := nil;
- s := UpperCase(Name);
- if s = 'BYTE' then Name := 'Byte'
- else if s = 'BOOLEAN' then Name := 'Boolean'
- else if s = 'CHAR' then Name := 'Char'
- else if s = 'INTEGER' then Name := 'Integer'
- else if s = 'INT64' then Name := 'Int64'
- else if s = 'LONGINT' then Name := 'LongInt'
- else if s = 'LONGWORD' then Name := 'LongWord'
- else if s = 'SHORTINT' then Name := 'ShortInt'
- else if s = 'SMALLINT' then Name := 'SmallInt'
- else if s = 'STRING' then Name := 'String'
- else if s = 'WORD' then Name := 'Word'
- else
- Ref := Engine.FindElement(Name);
- if Assigned(Ref) then
- begin
- {Result := TPasTypeRef(CreateElement(TPasTypeRef, Name, nil));
- TPasTypeRef(Result).RefType := Ref as TPasType;}
- Result := Ref as TPasType;
- Result.AddRef;
- end else
- Result := TPasUnresolvedTypeRef(CreateElement(TPasUnresolvedTypeRef, Name, nil));
- // !!!: Doesn't make sense for resolved types
- if Name = 'String' then
- begin
- NextToken;
- if CurToken = tkSquaredBraceOpen then
- begin
- // !!!: Parse the string length value and store it
- repeat
- NextToken;
- until CurToken = tkSquaredBraceClose;
- end else
- UngetToken;
- end;
- end;
- tkCaret:
- begin
- Result := TPasPointerType(CreateElement(TPasPointerType, '', Parent));
- TPasPointerType(Result).DestType := ParseType(nil);
- end;
- tkArray:
- begin
- Result := TPasArrayType(CreateElement(TPasArrayType, '', Parent));
- TPasArrayType(Result).IsPacked := HadPackedModifier;
- ParseArrayType(TPasArrayType(Result));
- end;
- tkBraceOpen:
- begin
- Result := TPasEnumType(CreateElement(TPasEnumType, '', Parent));
- while True do
- begin
- NextToken;
- EnumValue := TPasEnumValue(CreateElement(TPasEnumValue,
- CurTokenString, Result));
- TPasEnumType(Result).Values.Add(EnumValue);
- NextToken;
- if CurToken = tkBraceClose then
- break
- else if CurToken in [tkEqual,tkAssign] then
- begin
- EnumValue.AssignedValue:=ParseExpression;
- NextToken;
- if CurToken = tkBraceClose then
- Break
- else if not (CurToken=tkComma) then
- ParseExc(SParserExpectedCommaRBracket);
- end
- else if not (CurToken=tkComma) then
- ParseExc(SParserExpectedCommaRBracket)
- end;
- end;
- tkSet:
- begin
- Result := TPasSetType(CreateElement(TPasSetType, '', Parent));
- try
- ExpectToken(tkOf);
- TPasSetType(Result).EnumType := ParseType(Result);
- except
- Result.Free;
- raise;
- end;
- end;
- tkRecord:
- begin
- Result := TPasRecordType(CreateElement(TPasRecordType, '', Parent));
- TPasRecordType(Result).IsPacked := HadPackedModifier;
- try
- ParseRecordDecl(TPasRecordType(Result), False);
- except
- Result.Free;
- raise;
- end;
- end;
- tkProcedure:
- begin
- Result := TPasProcedureType(
- CreateElement(TPasProcedureType, '', Parent));
- try
- ParseProcedureOrFunctionHeader(Result,
- TPasProcedureType(Result), ptProcedure, True);
- except
- Result.Free;
- raise;
- end;
- end;
- tkFunction:
- begin
- Result := Engine.CreateFunctionType('', 'Result', Parent, False,
- Scanner.CurFilename, Scanner.CurRow);
- try
- ParseProcedureOrFunctionHeader(Result,
- TPasFunctionType(Result), ptFunction, True);
- except
- Result.Free;
- raise;
- end;
- end;
- else
- begin
- UngetToken;
- ParseRange;
- end;
- // ParseExc(SParserTypeSyntaxError);
- end;
- end;
- function TPasParser.ParseComplexType: TPasType;
- begin
- NextToken;
- case CurToken of
- tkProcedure:
- begin
- Result := TPasProcedureType(CreateElement(TPasProcedureType, '', nil));
- ParseProcedureOrFunctionHeader(Result,
- TPasProcedureType(Result), ptProcedure, True);
- UngetToken; // Unget semicolon
- end;
- tkFunction:
- begin
- Result := Engine.CreateFunctionType('', 'Result', nil, False,
- Scanner.CurFilename, Scanner.CurRow);
- ParseProcedureOrFunctionHeader(Result,
- TPasFunctionType(Result), ptFunction, True);
- UngetToken; // Unget semicolon
- end;
- else
- begin
- UngetToken;
- Result := ParseType(nil);
- exit;
- end;
- end;
- end;
- procedure TPasParser.ParseArrayType(Element: TPasArrayType);
- Var
- S : String;
- begin
- NextToken;
- S:='';
- case CurToken of
- tkSquaredBraceOpen:
- begin
- repeat
- NextToken;
- if CurToken<>tkSquaredBraceClose then
- S:=S+CurTokenText;
- until CurToken = tkSquaredBraceClose;
- Element.IndexRange:=S;
- ExpectToken(tkOf);
- Element.ElType := ParseType(nil);
- end;
- tkOf:
- begin
- NextToken;
- if CurToken = tkConst then
- // ArrayEl.AppendChild(Doc.CreateElement('const'))
- else
- begin
- UngetToken;
- Element.ElType := ParseType(nil);
- end
- end
- else
- ParseExc(SParserArrayTypeSyntaxError);
- end;
- end;
- function TPasParser.ParseExpression: String;
- var
- BracketLevel: Integer;
- MayAppendSpace, AppendSpace, NextAppendSpace: Boolean;
- begin
- SetLength(Result, 0);
- BracketLevel := 0;
- MayAppendSpace := False;
- AppendSpace := False;
- while True do
- begin
- NextToken;
- { !!!: Does not detect when normal brackets and square brackets are mixed
- in a wrong way. }
- if CurToken in [tkBraceOpen, tkSquaredBraceOpen] then
- Inc(BracketLevel)
- else if CurToken in [tkBraceClose, tkSquaredBraceClose] then
- begin
- if BracketLevel = 0 then
- break;
- Dec(BracketLevel);
- end else if (CurToken in [tkComma, tkSemicolon, tkColon, tkSquaredBraceClose,
- tkDotDot]) and (BracketLevel = 0) then
- break;
- if MayAppendSpace then
- begin
- NextAppendSpace := False;
- case CurToken of
- tkBraceOpen, tkBraceClose, tkDivision, tkEqual, tkCaret, tkAnd, tkAs,
- tkDiv, tkIn, tkIs, tkMinus, tkMod, tkMul, tkNot, tkOf, tkOn,
- tkOr, tkPlus, tkSHL, tkSHR, tkXOR:
- { tkPlus.._ASSIGNMENT, _UNEQUAL, tkPlusASN.._XORASN, _AS, _AT, _IN, _IS,
- tkOf, _ON, _OR, _AND, _DIV, _MOD, _NOT, _SHL, _SHR, _XOR:}
- begin
- AppendSpace := True;
- NextAppendSpace := True;
- end;
- end;
- if AppendSpace then
- Result := Result + ' ';
- AppendSpace := NextAppendSpace;
- end else
- MayAppendSpace := True;
- if CurToken=tkString then
- begin
- If (Length(CurTokenText)>0) and (CurTokenText[1]=#0) then
- Writeln('First char is null : "',CurTokenText,'"');
- Result := Result + ''''+StringReplace(CurTokenText,'''','''''',[rfReplaceAll])+''''
- end
- else
- Result := Result + CurTokenText;
- end;
- UngetToken;
- end;
- procedure TPasParser.AddProcOrFunction(ASection: TPasSection;
- AProc: TPasProcedure);
- var
- i: Integer;
- Member: TPasElement;
- OverloadedProc: TPasOverloadedProc;
- begin
- for i := 0 to ASection.Functions.Count - 1 do
- begin
- Member := TPasElement(ASection.Functions[i]);
- if CompareText(Member.Name, AProc.Name) = 0 then
- begin
- if Member.ClassType = TPasOverloadedProc then
- TPasOverloadedProc(Member).Overloads.Add(AProc)
- else
- begin
- OverloadedProc := TPasOverloadedProc.Create(AProc.Name, ASection);
- OverloadedProc.Overloads.Add(Member);
- OverloadedProc.Overloads.Add(AProc);
- ASection.Functions[i] := OverloadedProc;
- ASection.Declarations[ASection.Declarations.IndexOf(Member)] :=
- OverloadedProc;
- end;
- exit;
- end;
- end;
- // Not overloaded, so just add the proc/function to the lists
- ASection.Declarations.Add(AProc);
- ASection.Functions.Add(AProc);
- end;
- // Returns the parent for an element which is to be created
- function TPasParser.CheckIfOverloaded(AOwner: TPasClassType;
- const AName: String): TPasElement;
- var
- i: Integer;
- Member: TPasElement;
- begin
- for i := 0 to AOwner.Members.Count - 1 do
- begin
- Member := TPasElement(AOwner.Members[i]);
- if CompareText(Member.Name, AName) = 0 then
- begin
- if Member.ClassType = TPasOverloadedProc then
- Result := Member
- else
- begin
- Result := TPasOverloadedProc.Create(AName, AOwner);
- Result.Visibility := Member.Visibility;
- TPasOverloadedProc(Result).Overloads.Add(Member);
- AOwner.Members[i] := Result;
- end;
- exit;
- end;
- end;
- Result := AOwner;
- end;
- procedure TPasParser.ParseMain(var Module: TPasModule);
- begin
- NextToken;
- case CurToken of
- tkUnit: ParseUnit(Module);
- else
- ParseExc(Format(SParserExpectTokenError, ['unit']));
- end;
- end;
- // Starts after the "unit" token
- procedure TPasParser.ParseUnit(var Module: TPasModule);
- var
- CurBlock: TDeclType;
- Section: TPasSection;
- ConstEl: TPasConst;
- ResStrEl: TPasResString;
- TypeEl: TPasType;
- ClassEl: TPasClassType;
- List: TList;
- i,j: Integer;
- VarEl: TPasVariable;
- begin
- Module := nil;
- Module := TPasModule(CreateElement(TPasModule, ExpectIdentifier,
- Engine.Package));
- if Assigned(Engine.Package) then
- begin
- Module.PackageName := Engine.Package.Name;
- Engine.Package.Modules.Add(Module);
- end;
- ExpectToken(tkSemicolon);
- ExpectToken(tkInterface);
- Section := TPasSection(CreateElement(TPasSection, '', Module));
- Module.InterfaceSection := Section;
- CurBlock := declNone;
- while True do
- begin
- NextToken;
- if CurToken = tkImplementation then
- break;
- case CurToken of
- tkUses:
- ParseUsesList(Section);
- tkConst:
- CurBlock := declConst;
- tkResourcestring:
- CurBlock := declResourcestring;
- tkType:
- CurBlock := declType;
- tkVar:
- CurBlock := declVar;
- tkThreadVar:
- CurBlock := declThreadVar;
- tkProcedure:
- begin
- AddProcOrFunction(Section, ParseProcedureOrFunctionDecl(Section, ptProcedure));
- CurBlock := declNone;
- end;
- tkFunction:
- begin
- AddProcOrFunction(Section, ParseProcedureOrFunctionDecl(Section, ptFunction));
- CurBlock := declNone;
- end;
- tkProperty:
- begin
- ExpectIdentifier;
- ParseProperty(CreateElement(TPasProperty, CurTokenString, Section));
- end;
- tkOperator:
- begin
- AddProcOrFunction(Section, ParseProcedureOrFunctionDecl(Section, ptOperator));
- CurBlock := declNone;
- end;
- tkIdentifier:
- begin
- case CurBlock of
- declConst:
- begin
- ConstEl := ParseConstDecl(Section);
- Section.Declarations.Add(ConstEl);
- Section.Consts.Add(ConstEl);
- end;
- declResourcestring:
- begin
- ResStrEl := ParseResourcestringDecl(Section);
- Section.Declarations.Add(ResStrEl);
- Section.ResStrings.Add(ResStrEl);
- end;
- declType:
- begin
- TypeEl := ParseTypeDecl(Section);
- if Assigned(TypeEl) then // !!!
- begin
- Section.Declarations.Add(TypeEl);
- if TypeEl.ClassType = TPasClassType then
- begin
- // Remove previous forward declarations, if necessary
- for i := 0 to Section.Classes.Count - 1 do
- begin
- ClassEl := TPasClassType(Section.Classes[i]);
- if CompareText(ClassEl.Name, TypeEl.Name) = 0 then
- begin
- Section.Classes.Delete(i);
- for j := 0 to Section.Declarations.Count - 1 do
- if CompareText(TypeEl.Name,
- TPasElement(Section.Declarations[j]).Name) = 0 then
- begin
- Section.Declarations.Delete(j);
- break;
- end;
- ClassEl.Release;
- break;
- end;
- end;
- // Add the new class to the class list
- Section.Classes.Add(TypeEl)
- end else
- Section.Types.Add(TypeEl);
- end;
- end;
- declVar, declThreadVar:
- begin
- List := TList.Create;
- try
- try
- ParseVarDecl(Section, List);
- except
- for i := 0 to List.Count - 1 do
- TPasVariable(List[i]).Release;
- raise;
- end;
- for i := 0 to List.Count - 1 do
- begin
- VarEl := TPasVariable(List[i]);
- Section.Declarations.Add(VarEl);
- Section.Variables.Add(VarEl);
- end;
- finally
- List.Free;
- end;
- end;
- else
- ParseExc(SParserSyntaxError);
- end;
- end;
- else
- ParseExc(SParserInterfaceTokenError);
- end;
- end;
- end;
- // Starts after the "uses" token
- procedure TPasParser.ParseUsesList(ASection: TPasSection);
- var
- UnitName: String;
- Element: TPasElement;
- begin
- while True do
- begin
- UnitName := ExpectIdentifier;
- Element := Engine.FindModule(UnitName);
- if Assigned(Element) then
- Element.AddRef
- else
- Element := TPasType(CreateElement(TPasUnresolvedTypeRef, UnitName,
- ASection));
- ASection.UsesList.Add(Element);
- NextToken;
- if CurToken = tkSemicolon then
- break
- else if CurToken <> tkComma then
- ParseExc(SParserExpectedCommaSemicolon);
- end;
- end;
- // Starts after the variable name
- function TPasParser.ParseConstDecl(Parent: TPasElement): TPasConst;
- begin
- Result := TPasConst(CreateElement(TPasConst, CurTokenString, Parent));
- try
- NextToken;
- if CurToken = tkColon then
- Result.VarType := ParseType(nil)
- else
- UngetToken;
- ExpectToken(tkEqual);
- Result.Value := ParseExpression;
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- // Starts after the variable name
- function TPasParser.ParseResourcestringDecl(Parent: TPasElement): TPasResString;
- begin
- Result := TPasResString(CreateElement(TPasResString, CurTokenString, Parent));
- try
- ExpectToken(tkEqual);
- Result.Value := ParseExpression;
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- // Starts after the type name
- function TPasParser.ParseTypeDecl(Parent: TPasElement): TPasType;
- var
- TypeName: String;
- procedure ParseRange;
- begin
- Result := TPasRangeType(CreateElement(TPasRangeType, TypeName, Parent));
- try
- TPasRangeType(Result).RangeStart := ParseExpression;
- ExpectToken(tkDotDot);
- TPasRangeType(Result).RangeEnd := ParseExpression;
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- var
- EnumValue: TPasEnumValue;
- Prefix : String;
- HadPackedModifier : Boolean; // 12/04/04 - Dave - Added
- begin
- TypeName := CurTokenString;
- ExpectToken(tkEqual);
- NextToken;
- HadPackedModifier := False; { Assume not present }
- if CurToken = tkPacked then { If PACKED modifier }
- begin { Handle PACKED modifier for all situations }
- NextToken; { Move to next token for rest of parse }
- if CurToken in [tkArray, tkRecord, tkObject, tkClass] then { If allowed }
- HadPackedModifier := True { rememeber for later }
- else { otherwise, syntax error }
- ParseExc(Format(SParserExpectTokenError,['ARRAY, RECORD, OBJECT or CLASS']))
- end;
- case CurToken of
- tkRecord:
- begin
- Result := TPasRecordType(CreateElement(TPasRecordType, TypeName,
- Parent));
- try
- ParseRecordDecl(TPasRecordType(Result), False);
- ExpectToken(tkSemicolon);
- TPasRecordType(Result).IsPacked := HadPackedModifier;
- except
- Result.Free;
- raise;
- end;
- end;
- tkObject:
- begin
- Result := ParseClassDecl(Parent, TypeName, okObject);
- TPasClassType(Result).IsPacked := HadPackedModifier;
- end;
- tkClass:
- begin
- Result := ParseClassDecl(Parent, TypeName, okClass);
- { could be TPasClassOfType }
- if result is TPasClassType then
- TPasClassType(Result).IsPacked := HadPackedModifier;
- end;
- tkInterface:
- Result := ParseClassDecl(Parent, TypeName, okInterface);
- tkCaret:
- begin
- Result := TPasPointerType(CreateElement(TPasPointerType, TypeName,
- Parent));
- try
- TPasPointerType(Result).DestType := ParseType(nil);
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- tkIdentifier:
- begin
- Prefix:=CurTokenString;
- NextToken;
- if CurToken = tkDot then
- begin
- ExpectIdentifier;
- NextToken;
- end
- else
- Prefix:='';
- if CurToken = tkSemicolon then
- begin
- UngetToken;
- UngetToken;
- Result := TPasAliasType(CreateElement(TPasAliasType, TypeName,
- Parent));
- try
- TPasAliasType(Result).DestType := ParseType(nil,Prefix);
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end else if CurToken = tkSquaredBraceOpen then
- begin
- // !!!: Check for string type and store string length somewhere
- Result := TPasAliasType(CreateElement(TPasAliasType, TypeName,
- Parent));
- try
- TPasAliasType(Result).DestType :=
- TPasUnresolvedTypeRef.Create(CurTokenString, Parent);
- ParseExpression;
- ExpectToken(tkSquaredBraceClose);
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end else
- begin
- UngetToken;
- UngetToken;
- ParseRange;
- end;
- end;
- { _STRING, _FILE:
- begin
- Result := TPasAliasType(CreateElement(TPasAliasType, TypeName, Parent));
- UngetToken;
- TPasAliasType(Result).DestType := ParseType(nil);
- ExpectToken(tkSemicolon);
- end;}
- tkArray:
- begin
- Result := TPasArrayType(CreateElement(TPasArrayType, TypeName, Parent));
- try
- ParseArrayType(TPasArrayType(Result));
- TPasArrayType(Result).IsPacked := HadPackedModifier;
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- tkSet:
- begin
- Result := TPasSetType(CreateElement(TPasSetType, TypeName, Parent));
- try
- ExpectToken(tkOf);
- TPasSetType(Result).EnumType := ParseType(Result);
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- tkBraceOpen:
- begin
- Result := TPasEnumType(CreateElement(TPasEnumType, TypeName, Parent));
- try
- while True do
- begin
- NextToken;
- EnumValue := TPasEnumValue(CreateElement(TPasEnumValue,
- CurTokenString, Result));
- TPasEnumType(Result).Values.Add(EnumValue);
- NextToken;
- if CurToken = tkBraceClose then
- break
- else if CurToken in [tkEqual,tkAssign] then
- begin
- EnumValue.AssignedValue:=ParseExpression;
- NextToken;
- if CurToken = tkBraceClose then
- Break
- else if not (CurToken=tkComma) then
- ParseExc(SParserExpectedCommaRBracket);
- end
- else if not (CurToken=tkComma) then
- ParseExc(SParserExpectedCommaRBracket)
- end;
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- tkProcedure:
- begin
- Result := TPasProcedureType(CreateElement(TPasProcedureType, TypeName,
- Parent));
- try
- ParseProcedureOrFunctionHeader(Result,
- TPasProcedureType(Result), ptProcedure, True);
- except
- Result.Free;
- raise;
- end;
- end;
- tkFunction:
- begin
- Result := Engine.CreateFunctionType(TypeName, 'Result', Parent, False,
- Scanner.CurFilename, Scanner.CurRow);
- try
- ParseProcedureOrFunctionHeader(Result,
- TPasFunctionType(Result), ptFunction, True);
- except
- Result.Free;
- raise;
- end;
- end;
- tkType:
- begin
- Result := TPasTypeAliasType(CreateElement(TPasTypeAliasType, TypeName,
- Parent));
- try
- TPasTypeAliasType(Result).DestType := ParseType(nil);
- ExpectToken(tkSemicolon);
- except
- Result.Free;
- raise;
- end;
- end;
- else
- begin
- UngetToken;
- ParseRange;
- end;
- end;
- end;
- // Starts after the variable name
- procedure TPasParser.ParseInlineVarDecl(Parent: TPasElement; VarList: TList);
- begin
- ParseInlineVarDecl(Parent, VarList, visDefault, False);
- end;
- procedure TPasParser.ParseInlineVarDecl(Parent: TPasElement; VarList: TList;
- AVisibility: TPasMemberVisibility; ClosingBrace: Boolean);
- var
- VarNames: TStringList;
- i: Integer;
- VarType: TPasType;
- VarEl: TPasVariable;
- begin
- VarNames := TStringList.Create;
- try
- while True do
- begin
- VarNames.Add(CurTokenString);
- NextToken;
- if CurToken = tkColon then
- break
- else if CurToken <> tkComma then
- ParseExc(SParserExpectedCommaColon);
- ExpectIdentifier;
- end;
- VarType := ParseComplexType;
- for i := 0 to VarNames.Count - 1 do
- begin
- VarEl := TPasVariable(CreateElement(TPasVariable, VarNames[i], Parent,
- AVisibility));
- VarEl.VarType := VarType;
- if i > 0 then
- VarType.AddRef;
- VarList.Add(VarEl);
- end;
- NextToken;
- // Records may be terminated with end, no semicolon
- if (CurToken <> tkEnd) and (CurToken <> tkSemicolon) and not
- (ClosingBrace and (CurToken = tkBraceClose)) then
- ParseExc(SParserExpectedSemiColonEnd);
- finally
- VarNames.Free;
- end;
- end;
- // Starts after the variable name
- procedure TPasParser.ParseVarDecl(Parent: TPasElement; List: TList);
- var
- i: Integer;
- VarType: TPasType;
- Value, S: String;
- M: string;
- begin
- while True do
- begin
- List.Add(CreateElement(TPasVariable, CurTokenString, Parent));
- NextToken;
- if CurToken = tkColon then
- break
- else if CurToken <> tkComma then
- ParseExc(SParserExpectedCommaColon);
- ExpectIdentifier;
- end;
- VarType := ParseComplexType;
- for i := 0 to List.Count - 1 do
- begin
- TPasVariable(List[i]).VarType := VarType;
- if i > 0 then
- VarType.AddRef;
- end;
- NextToken;
- If CurToken=tkEqual then
- begin
- Value := ParseExpression;
- for i := 0 to List.Count - 1 do
- TPasVariable(List[i]).Value := Value;
- end
- else
- UngetToken;
- NextToken;
- if CurToken = tkAbsolute then
- begin
- // !!!: Store this information
- ExpectIdentifier;
- end else
- UngetToken;
- ExpectToken(tkSemicolon);
- M := '';
- while True do
- begin
- NextToken;
- if CurToken = tkIdentifier then
- begin
- s := UpperCase(CurTokenText);
- if s = 'CVAR' then
- begin
- M := M + '; cvar';
- ExpectToken(tkSemicolon);
- end
- else if (s = 'EXTERNAL') or (s = 'PUBLIC') or (s = 'EXPORT') then
- begin
- M := M + ';' + CurTokenText;
- if s = 'EXTERNAL' then
- begin
- NextToken;
- if ((CurToken = tkString) or (CurToken = tkIdentifier)) and (UpperCase(CurTokenText)<> 'NAME') then
- begin
- // !!!: Is this really correct for tkString?
- M := M + ' ' + CurTokenText;
- NextToken;
- end;
- end
- else
- NextToken;
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'NAME') then
- begin
- M := M + ' name ';
- NextToken;
- if (CurToken = tkString) or (CurToken = tkIdentifier) then
- // !!!: Is this really correct for tkString?
- M := M + CurTokenText
- else
- ParseExc(SParserSyntaxError);
- ExpectToken(tkSemicolon);
- end
- else if CurToken <> tkSemicolon then
- ParseExc(SParserSyntaxError);
- end else
- begin
- UngetToken;
- break;
- end
- end else
- begin
- UngetToken;
- break;
- end;
- end; // while
- if M <> '' then
- for i := 0 to List.Count - 1 do
- TPasVariable(List[i]).Modifiers := M;
- end;
- // Starts after the opening bracket token
- procedure TPasParser.ParseArgList(Parent: TPasElement; Args: TList; EndToken: TToken);
- var
- ArgNames: TStringList;
- IsUntyped: Boolean;
- Name, Value: String;
- i: Integer;
- Arg: TPasArgument;
- Access: TArgumentAccess;
- ArgType: TPasType;
- begin
- while True do
- begin
- ArgNames := TStringList.Create;
- Access := argDefault;
- IsUntyped := False;
- ArgType := nil;
- while True do
- begin
- NextToken;
- if CurToken = tkConst then
- begin
- Access := argConst;
- Name := ExpectIdentifier;
- end else if CurToken = tkVar then
- begin
- Access := ArgVar;
- Name := ExpectIdentifier;
- end else if (CurToken = tkIdentifier) and (UpperCase(CurTokenString) = 'OUT') then
- begin
- Access := ArgOut;
- Name := ExpectIdentifier;
- end else if CurToken = tkIdentifier then
- Name := CurTokenString
- else
- ParseExc(SParserExpectedConstVarID);
- ArgNames.Add(Name);
- NextToken;
- if CurToken = tkColon then
- break
- else if ((CurToken = tkSemicolon) or (CurToken = tkBraceClose)) and
- (Access <> argDefault) then
- begin
- // found an untyped const or var argument
- UngetToken;
- IsUntyped := True;
- break
- end
- else if CurToken <> tkComma then
- ParseExc(SParserExpectedCommaColon);
- end;
- SetLength(Value, 0);
- if not IsUntyped then
- begin
- ArgType := ParseType(nil);
- NextToken;
- if CurToken = tkEqual then
- begin
- Value := ParseExpression;
- end else
- UngetToken;
- end;
- for i := 0 to ArgNames.Count - 1 do
- begin
- Arg := TPasArgument(CreateElement(TPasArgument, ArgNames[i], Parent));
- Arg.Access := Access;
- Arg.ArgType := ArgType;
- if (i > 0) and Assigned(ArgType) then
- ArgType.AddRef;
- Arg.Value := Value;
- Args.Add(Arg);
- end;
- ArgNames.Free;
- NextToken;
- if CurToken = EndToken then
- break;
- end;
- end;
- // Next token is expected to be a "(", ";" or for a function ":". The caller
- // will get the token after the final ";" as next token.
- procedure TPasParser.ParseProcedureOrFunctionHeader(Parent: TPasElement;
- Element: TPasProcedureType; ProcType: TProcType; OfObjectPossible: Boolean);
- begin
- NextToken;
- case ProcType of
- ptFunction:
- begin
- if CurToken = tkBraceOpen then
- begin
- NextToken;
- if (CurToken = tkBraceClose) then
- else
- begin
- UngetToken;
- ParseArgList(Parent, Element.Args, tkBraceClose);
- end;
- ExpectToken(tkColon);
- end else if CurToken <> tkColon then
- ParseExc(SParserExpectedLBracketColon);
- if Assigned(Element) then // !!!
- TPasFunctionType(Element).ResultEl.ResultType := ParseType(Parent)
- else
- ParseType(nil);
- end;
- ptProcedure:
- begin
- if CurToken = tkBraceOpen then
- begin
- NextToken;
- if (CurToken = tkBraceClose) then
- else
- begin
- UngetToken;
- ParseArgList(Element, Element.Args, tkBraceClose);
- end
- end else if (CurToken = tkSemicolon) or (OfObjectPossible and (CurToken = tkOf)) then
- UngetToken
- else
- ParseExc(SParserExpectedLBracketSemicolon);
- end;
- ptOperator:
- begin
- ParseArgList(Element, Element.Args, tkBraceClose);
- TPasFunctionType(Element).ResultEl.Name := ExpectIdentifier;
- ExpectToken(tkColon);
- if Assigned(Element) then // !!!
- TPasFunctionType(Element).ResultEl.ResultType := ParseType(Parent)
- else
- ParseType(nil);
- end;
- end;
- NextToken;
- if OfObjectPossible and (CurToken = tkOf) then
- begin
- ExpectToken(tkObject);
- Element.IsOfObject := True;
- end else
- UngetToken;
- NextToken;
- if CurToken = tkEqual then
- begin
- // for example: const p: procedure = nil;
- UngetToken;
- exit;
- end else
- UngetToken;
- ExpectToken(tkSemicolon);
- while True do
- begin
- NextToken;
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenString) = 'CDECL') then
- begin
- { El['calling-conv'] := 'cdecl';}
- ExpectToken(tkSemicolon);
- end else if (CurToken = tkIdentifier) and (UpperCase(CurTokenString) = 'STDCALL') then
- begin
- { El['calling-conv'] := 'stdcall';}
- ExpectToken(tkSemicolon);
- end else if (CurToken = tkInline) then
- begin
- { TPasProcedure(Parent).IsInline := True;}
- ExpectToken(tkSemicolon);
- end else if (CurToken = tkIdentifier) and (UpperCase(CurTokenString) = 'DEPRECATED') then
- begin
- { El['calling-conv'] := 'cdecl';}
- ExpectToken(tkSemicolon);
- end else if (CurToken = tkIdentifier) and (UpperCase(CurTokenString) = 'EXTERNAL') then
- begin
- repeat
- NextToken
- until CurToken = tkSemicolon;
- end else if (CurToken = tkSquaredBraceOpen) then
- begin
- repeat
- NextToken
- until CurToken = tkSquaredBraceClose;
- ExpectToken(tkSemicolon);
- end else if Parent.InheritsFrom(TPasProcedure) and
- (CurToken = tkIdentifier) and (UpperCase(CurTokenString) = 'OVERLOAD') then
- begin
- TPasProcedure(Parent).IsOverload := True;
- ExpectToken(tkSemicolon);
- end else
- begin
- UngetToken;
- break;
- end;
- end;
- end;
- procedure TPasParser.ParseProperty(Element:TPasElement);
- function GetAccessorName: String;
- begin
- ExpectIdentifier;
- Result := CurTokenString;
- while True do
- begin
- NextToken;
- if CurToken = tkDot then
- begin
- ExpectIdentifier;
- Result := Result + '.' + CurTokenString;
- end else
- break;
- end;
- UngetToken;
- end;
- begin
- NextToken;
- // !!!: Parse array properties correctly
- if CurToken = tkSquaredBraceOpen then
- begin
- ParseArgList(Element, TPasProperty(Element).Args, tkSquaredBraceClose);
- NextToken;
- end;
- if CurToken = tkColon then
- begin
- // read property type
- TPasProperty(Element).VarType := ParseType(Element);
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- // read 'index' access modifier
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'INDEX') then
- TPasProperty(Element).IndexValue := ParseExpression
- else
- UngetToken;
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- // read 'read' access modifier
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'READ') then
- TPasProperty(Element).ReadAccessorName := GetAccessorName
- else
- UngetToken;
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- // read 'write' access modifier
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'WRITE') then
- TPasProperty(Element).WriteAccessorName := GetAccessorName
- else
- UngetToken;
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- // read 'stored' access modifier
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'STORED') then
- begin
- NextToken;
- if CurToken = tkTrue then
- TPasProperty(Element).StoredAccessorName := 'True'
- else if CurToken = tkFalse then
- TPasProperty(Element).StoredAccessorName := 'False'
- else if CurToken = tkIdentifier then
- TPasProperty(Element).StoredAccessorName := CurTokenString
- else
- ParseExc(SParserSyntaxError);
- end else
- UngetToken;
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- // read 'default' value modifier
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'DEFAULT') then
- TPasProperty(Element).DefaultValue := ParseExpression
- else
- UngetToken;
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- // read 'nodefault' modifier
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'NODEFAULT') then
- begin
- TPasProperty(Element).IsNodefault:=true;
- end;
- NextToken;
- end;
- if CurToken = tkSemicolon then
- begin
- // read semicolon
- NextToken;
- end;
- if (CurToken = tkIdentifier) and (UpperCase(CurTokenText) = 'DEFAULT') then
- begin
- NextToken;
- if CurToken = tkSemicolon then
- begin
- TPasProperty(Element).IsDefault := True;
- UngetToken;
- end else
- begin
- UngetToken;
- TPasProperty(Element).DefaultValue := ParseExpression;
- end;
- end else
- UngetToken;
- end;
- // Starts after the "procedure" or "function" token
- function TPasParser.ParseProcedureOrFunctionDecl(Parent: TPasElement;
- ProcType: TProcType): TPasProcedure;
- var
- Name: String;
- i: Integer;
- begin
- case ProcType of
- ptFunction:
- begin
- Name := ExpectIdentifier;
- Result := TPasFunction(CreateElement(TPasFunction, Name, Parent));
- Result.ProcType := Engine.CreateFunctionType('', 'Result', Result, True,
- Scanner.CurFilename, Scanner.CurRow);
- end;
- ptProcedure:
- begin
- Name := ExpectIdentifier;
- Result := TPasProcedure(CreateElement(TPasProcedure, Name, Parent));
- Result.ProcType := TPasProcedureType(CreateElement(TPasProcedureType, '',
- Result));
- end;
- ptOperator:
- begin
- NextToken;
- Name := 'operator ' + TokenInfos[CurToken];
- Result := TPasOperator(CreateElement(TPasOperator, Name, Parent));
- Result.ProcType := Engine.CreateFunctionType('', '__INVALID__', Result,
- True, Scanner.CurFilename, Scanner.CurRow);
- end;
- end;
- ParseProcedureOrFunctionHeader(Result, Result.ProcType, ProcType, False);
- if ProcType = ptOperator then
- begin
- Result.Name := Result.Name + '(';
- for i := 0 to Result.ProcType.Args.Count - 1 do
- begin
- if i > 0 then
- Result.Name := Result.Name + ', ';
- Result.Name := Result.Name +
- TPasArgument(Result.ProcType.Args[i]).ArgType.Name;
- end;
- Result.Name := Result.Name + '): ' +
- TPasFunctionType(Result.ProcType).ResultEl.ResultType.Name;
- end;
- end;
- // Starts after the "record" token
- procedure TPasParser.ParseRecordDecl(Parent: TPasRecordType; IsNested: Boolean);
- var
- VariantName: String;
- Variant: TPasVariant;
- begin
- while True do
- begin
- if IsNested then
- begin
- if CurToken = tkBraceClose then
- break;
- NextToken;
- if CurToken = tkBraceClose then
- break;
- end else
- begin
- if CurToken = tkEnd then
- break;
- NextToken;
- if CurToken = tkEnd then
- break;
- end;
- if CurToken = tkCase then
- begin
- ExpectToken(tkIdentifier);
- VariantName := CurTokenString;
- NextToken;
- if CurToken = tkColon then
- Parent.VariantName := VariantName
- else
- begin
- UngetToken;
- UngetToken;
- end;
- Parent.VariantType := ParseType(Parent);
- Parent.Variants := TList.Create;
- ExpectToken(tkOf);
- while True do
- begin
- Variant := TPasVariant(CreateElement(TPasVariant, '', Parent));
- Parent.Variants.Add(Variant);
- Variant.Values := TStringList.Create;
- while True do
- begin
- Variant.Values.Add(ParseExpression);
- NextToken;
- if CurToken = tkColon then
- break
- else if CurToken <> tkComma then
- ParseExc(SParserExpectedCommaColon);
- end;
- ExpectToken(tkBraceOpen);
- Variant.Members := TPasRecordType(CreateElement(TPasRecordType, '',
- Variant));
- try
- ParseRecordDecl(Variant.Members, True);
- except
- Variant.Members.Free;
- raise;
- end;
- NextToken;
- if CurToken = tkSemicolon then
- NextToken;
- if (CurToken = tkEnd) or (CurToken = tkBraceClose) then
- break
- else
- UngetToken;
- end
- end else
- ParseInlineVarDecl(Parent, Parent.Members, visDefault, IsNested);
- end;
- end;
- // Starts after the "class" token
- function TPasParser.ParseClassDecl(Parent: TPasElement;
- const AClassName: String; AObjKind: TPasObjKind): TPasType;
- var
- CurVisibility: TPasMemberVisibility;
- procedure ProcessMethod(const MethodTypeName: String; HasReturnValue: Boolean);
- var
- Owner: TPasElement;
- Proc: TPasProcedure;
- s: String;
- pt: TProcType;
- begin
- ExpectIdentifier;
- Owner := CheckIfOverloaded(TPasClassType(Result), CurTokenString);
- if HasReturnValue then
- begin
- Proc := TPasFunction(CreateElement(TPasFunction, CurTokenString, Owner,
- CurVisibility));
- Proc.ProcType := Engine.CreateFunctionType('', 'Result', Proc, True,
- Scanner.CurFilename, Scanner.CurRow);
- end else
- begin
- // !!!: The following is more than ugly
- if MethodTypeName = 'constructor' then
- Proc := TPasConstructor(CreateElement(TPasConstructor, CurTokenString,
- Owner, CurVisibility))
- else if MethodTypeName = 'destructor' then
- Proc := TPasDestructor(CreateElement(TPasDestructor, CurTokenString,
- Owner, CurVisibility))
- else
- Proc := TPasProcedure(CreateElement(TPasProcedure, CurTokenString,
- Owner, CurVisibility));
- Proc.ProcType := TPasProcedureType(CreateElement(TPasProcedureType, '',
- Proc, CurVisibility));
- end;
- if Owner.ClassType = TPasOverloadedProc then
- TPasOverloadedProc(Owner).Overloads.Add(Proc)
- else
- TPasClassType(Result).Members.Add(Proc);
- if HasReturnValue then
- pt := ptFunction
- else
- pt := ptProcedure;
- ParseProcedureOrFunctionHeader(Proc, Proc.ProcType, pt, False);
- while True do
- begin
- NextToken;
- if CurToken = tkIdentifier then
- begin
- s := UpperCase(CurTokenString);
- if s = 'VIRTUAL' then
- Proc.IsVirtual := True
- else if s = 'DYNAMIC' then
- Proc.IsDynamic := True
- else if s = 'ABSTRACT' then
- Proc.IsAbstract := True
- else if s = 'OVERRIDE' then
- Proc.IsOverride := True
- else if s = 'OVERLOAD' then
- Proc.IsOverload := True
- else if s = 'MESSAGE' then
- begin
- Proc.IsMessage := True;
- repeat
- NextToken;
- until CurToken = tkSemicolon;
- UngetToken;
- end else if s = 'CDECL' then
- { El['calling-conv'] := 'cdecl';}
- else if s = 'STDCALL' then
- { El['calling-conv'] := 'stdcall';}
- else
- begin
- UngetToken;
- break;
- end;
- ExpectToken(tkSemicolon);
- end else
- begin
- UngetToken;
- break;
- end;
- end;
- end;
- var
- s, SourceFilename: String;
- i, SourceLinenumber: Integer;
- VarList: TList;
- Element: TPasElement;
- begin
- // Save current parsing position to get it correct in all cases
- SourceFilename := Scanner.CurFilename;
- SourceLinenumber := Scanner.CurRow;
- NextToken;
- if (AObjKind = okClass) and (CurToken = tkOf) then
- begin
- Result := TPasClassOfType(Engine.CreateElement(TPasClassOfType, AClassName,
- Parent, SourceFilename, SourceLinenumber));
- ExpectIdentifier;
- UngetToken; // Only names are allowed as following type
- TPasClassOfType(Result).DestType := ParseType(Result);
- ExpectToken(tkSemicolon);
- exit;
- end;
- Result := TPasClassType(Engine.CreateElement(TPasClassType, AClassName,
- Parent, SourceFilename, SourceLinenumber));
- try
- TPasClassType(Result).ObjKind := AObjKind;
- // Parse ancestor list
- if CurToken = tkBraceOpen then
- begin
- TPasClassType(Result).AncestorType := ParseType(nil);
- while True do
- begin
- NextToken;
- if CurToken = tkBraceClose then
- break;
- UngetToken;
- ExpectToken(tkComma);
- ExpectIdentifier;
- // !!!: Store interface name
- end;
- NextToken;
- end;
- if CurToken <> tkSemicolon then
- begin
- CurVisibility := visDefault;
- while CurToken <> tkEnd do
- begin
- case CurToken of
- tkIdentifier:
- begin
- s := LowerCase(CurTokenString);
- if s = 'private' then
- CurVisibility := visPrivate
- else if s = 'protected' then
- CurVisibility := visProtected
- else if s = 'public' then
- CurVisibility := visPublic
- else if s = 'published' then
- CurVisibility := visPublished
- else if s = 'automated' then
- CurVisibility := visAutomated
- else
- begin
- VarList := TList.Create;
- try
- ParseInlineVarDecl(Result, VarList, CurVisibility, False);
- for i := 0 to VarList.Count - 1 do
- begin
- Element := TPasElement(VarList[i]);
- Element.Visibility := CurVisibility;
- TPasClassType(Result).Members.Add(Element);
- end;
- finally
- VarList.Free;
- end;
- end;
- end;
- tkProcedure:
- ProcessMethod('procedure', False);
- tkFunction:
- ProcessMethod('function', True);
- tkConstructor:
- ProcessMethod('constructor', False);
- tkDestructor:
- ProcessMethod('destructor', False);
- tkProperty:
- begin
- ExpectIdentifier;
- Element := CreateElement(TPasProperty, CurTokenString, Result, CurVisibility);
- TPasClassType(Result).Members.Add(Element);
- ParseProperty(Element);
- end;
- end; // end case
- NextToken;
- end;
- // Eat semicolon after class...end
- ExpectToken(tkSemicolon);
- end;
- except
- Result.Free;
- raise;
- end;
- end;
- function TPasParser.CreateElement(AClass: TPTreeElement; const AName: String;
- AParent: TPasElement): TPasElement;
- begin
- Result := Engine.CreateElement(AClass, AName, AParent,
- Scanner.CurFilename, Scanner.CurRow);
- end;
- function TPasParser.CreateElement(AClass: TPTreeElement; const AName: String;
- AParent: TPasElement; AVisibility: TPasMemberVisibility): TPasElement;
- begin
- Result := Engine.CreateElement(AClass, AName, AParent, AVisibility,
- Scanner.CurFilename, Scanner.CurRow);
- end;
- function ParseSource(AEngine: TPasTreeContainer;
- const FPCCommandLine, OSTarget, CPUTarget: String): TPasModule;
- var
- FileResolver: TFileResolver;
- Parser: TPasParser;
- Start, CurPos: PChar;
- Filename: String;
- Scanner: TPascalScanner;
- procedure ProcessCmdLinePart;
- var
- l: Integer;
- s: String;
- begin
- l := CurPos - Start;
- SetLength(s, l);
- if l > 0 then
- Move(Start^, s[1], l)
- else
- exit;
- if s[1] = '-' then
- begin
- case s[2] of
- 'd':
- Scanner.Defines.Append(UpperCase(Copy(s, 3, Length(s))));
- 'F':
- if s[3] = 'i' then
- FileResolver.AddIncludePath(Copy(s, 4, Length(s)));
- 'S':
- if s[3]='d' then
- begin
- include(Scanner.Options,po_delphi);
- include(Parser.Options,po_delphi);
- end;
- end;
- end else
- if Filename <> '' then
- raise Exception.Create(SErrMultipleSourceFiles)
- else
- Filename := s;
- end;
- var
- s: String;
- begin
- Result := nil;
- FileResolver := nil;
- Scanner := nil;
- Parser := nil;
- try
- FileResolver := TFileResolver.Create;
- Scanner := TPascalScanner.Create(FileResolver);
- Scanner.Defines.Append('FPK');
- Scanner.Defines.Append('FPC');
- s := UpperCase(OSTarget);
- Scanner.Defines.Append(s);
- if s = 'LINUX' then
- Scanner.Defines.Append('UNIX')
- else if s = 'FREEBSD' then
- begin
- Scanner.Defines.Append('BSD');
- Scanner.Defines.Append('UNIX');
- end else if s = 'NETBSD' then
- begin
- Scanner.Defines.Append('BSD');
- Scanner.Defines.Append('UNIX');
- end else if s = 'SUNOS' then
- begin
- Scanner.Defines.Append('SOLARIS');
- Scanner.Defines.Append('UNIX');
- end else if s = 'GO32V2' then
- Scanner.Defines.Append('DPMI')
- else if s = 'BEOS' then
- Scanner.Defines.Append('UNIX')
- else if s = 'QNX' then
- Scanner.Defines.Append('UNIX');
- Parser := TPasParser.Create(Scanner, FileResolver, AEngine);
- Filename := '';
- if FPCCommandLine<>'' then
- begin
- Start := @FPCCommandLine[1];
- CurPos := Start;
- while CurPos[0] <> #0 do
- begin
- if CurPos[0] = ' ' then
- begin
- ProcessCmdLinePart;
- Start := CurPos + 1;
- end;
- Inc(CurPos);
- end;
- ProcessCmdLinePart;
- end;
- if Filename = '' then
- raise Exception.Create(SErrNoSourceGiven);
- Scanner.OpenFile(Filename);
- Parser.ParseMain(Result);
- finally
- Parser.Free;
- Scanner.Free;
- FileResolver.Free;
- end;
- end;
- end.
|