123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097 |
- {
- $Id$
- Copyright (c) 1998-2002 by Florian Klaempfl, Daniel Mantione
- Does the parsing of the procedures/functions
- This program is free software; you can redistribute it and/or modify
- it under the terms of the GNU General Public License as published by
- the Free Software Foundation; either version 2 of the License, or
- (at your option) any later version.
- 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. See the
- GNU General Public License for more details.
- You should have received a copy of the GNU General Public License
- along with this program; if not, write to the Free Software
- Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
- ****************************************************************************
- }
- unit pdecsub;
- {$i fpcdefs.inc}
- interface
- uses
- tokens,symconst,symtype,symdef,symsym;
- const
- pd_global = $1; { directive must be global }
- pd_body = $2; { directive needs a body }
- pd_implemen = $4; { directive can be used implementation section }
- pd_interface = $8; { directive can be used interface section }
- pd_object = $10; { directive can be used object declaration }
- pd_procvar = $20; { directive can be used procvar declaration }
- pd_notobject = $40; { directive can not be used object declaration }
- pd_notobjintf= $80; { directive can not be used interface declaration }
- function is_proc_directive(tok:ttoken):boolean;
- procedure parameter_dec(aktprocdef:tabstractprocdef);
- procedure parse_proc_directives(var pdflags:word);
- procedure handle_calling_convention(sym:tprocsym;def:tabstractprocdef);
- procedure calc_parasymtable_addresses(def:tprocdef);
- procedure parse_proc_head(options:tproctypeoption);
- procedure parse_proc_dec;
- procedure parse_var_proc_directives(var sym : tsym);
- procedure parse_object_proc_directives(var sym : tprocsym);
- function proc_add_definition(aprocsym:tprocsym;var aprocdef : tprocdef) : boolean;
- implementation
- uses
- {$ifdef delphi}
- sysutils,
- {$else delphi}
- strings,
- {$endif delphi}
- { common }
- cutils,cclasses,
- { global }
- globtype,globals,verbose,
- systems,cpubase,
- { aasm }
- aasmbase,aasmtai,aasmcpu,
- { symtable }
- symbase,symtable,defbase,paramgr,
- { pass 1 }
- node,htypechk,
- nmat,nadd,ncal,nset,ncnv,ninl,ncon,nld,nflw,
- { parser }
- fmodule,scanner,
- pbase,pexpr,ptype,pdecl,
- { linking }
- import,gendef,
- { codegen }
- cpuinfo,cgbase
- ;
- procedure resetvaluepara(p:tnamedindexitem;arg:pointer);
- begin
- if tsym(p).typ=varsym then
- with tvarsym(p) do
- if copy(name,1,3)='val' then
- aktprocdef.parast.symsearch.rename(name,copy(name,4,length(name)));
- end;
- procedure parameter_dec(aktprocdef:tabstractprocdef);
- {
- handle_procvar needs the same changes
- }
- var
- is_procvar : boolean;
- sc : tidstringlist;
- s : string;
- hpos,
- storetokenpos : tfileposinfo;
- htype,
- tt : ttype;
- hvs,
- vs : tvarsym;
- srsym : tsym;
- hs1 : string;
- varspez : Tvarspez;
- inserthigh : boolean;
- tdefaultvalue : tconstsym;
- defaultrequired : boolean;
- old_object_option : tsymoptions;
- begin
- { reset }
- defaultrequired:=false;
- { parsing a proc or procvar ? }
- is_procvar:=(aktprocdef.deftype=procvardef);
- consume(_LKLAMMER);
- { Delphi/Kylix supports nonsense like }
- { procedure p(); }
- if try_to_consume(_RKLAMMER) and
- not(m_tp7 in aktmodeswitches) then
- exit;
- { the variables are always public }
- old_object_option:=current_object_option;
- current_object_option:=[sp_public];
- inc(testcurobject);
- repeat
- if try_to_consume(_VAR) then
- varspez:=vs_var
- else
- if try_to_consume(_CONST) then
- varspez:=vs_const
- else
- if (idtoken=_OUT) and (m_out in aktmodeswitches) then
- begin
- consume(_OUT);
- varspez:=vs_out
- end
- else
- varspez:=vs_value;
- inserthigh:=false;
- tdefaultvalue:=nil;
- tt.reset;
- { self is only allowed in procvars and class methods }
- if (idtoken=_SELF) and
- (is_procvar or
- (assigned(procinfo._class) and is_class(procinfo._class))) then
- begin
- if varspez <> vs_value then
- CGMessage(parser_e_self_call_by_value);
- if not is_procvar then
- begin
- htype.setdef(procinfo._class);
- vs:=tvarsym.create('@',htype);
- vs.varspez:=vs_var;
- { insert the sym in the parasymtable }
- tprocdef(aktprocdef).parast.insert(vs);
- inc(procinfo.selfpointer_offset,vs.address);
- end
- else
- vs:=nil;
- { must also be included for procvars to allow the proc2procvar }
- { type conversions (po_containsself is in po_comp) (JM) }
- include(aktprocdef.procoptions,po_containsself);
- consume(idtoken);
- consume(_COLON);
- single_type(tt,hs1,false);
- { this must be call-by-value, but we generate already an }
- { an error above if that's not the case (JM) }
- aktprocdef.concatpara(tt,vs,varspez,nil);
- { check the types for procedures only }
- if not is_procvar then
- CheckTypes(tt.def,procinfo._class);
- end
- else
- begin
- { read identifiers }
- sc:=consume_idlist;
- {$ifdef fixLeaksOnError}
- strContStack.push(sc);
- {$endif fixLeaksOnError}
- { read type declaration, force reading for value and const paras }
- if (token=_COLON) or (varspez=vs_value) then
- begin
- consume(_COLON);
- { check for an open array }
- if token=_ARRAY then
- begin
- consume(_ARRAY);
- consume(_OF);
- { define range and type of range }
- tt.setdef(tarraydef.create(0,-1,s32bittype));
- { array of const ? }
- if (token=_CONST) and (m_objpas in aktmodeswitches) then
- begin
- consume(_CONST);
- srsym:=searchsymonlyin(systemunit,'TVARREC');
- if not assigned(srsym) then
- InternalError(1234124);
- tarraydef(tt.def).elementtype:=ttypesym(srsym).restype;
- tarraydef(tt.def).IsArrayOfConst:=true;
- end
- else
- begin
- { define field type }
- single_type(tarraydef(tt.def).elementtype,hs1,false);
- end;
- inserthigh:=true;
- end
- else
- begin
- { open string ? }
- if (varspez=vs_var) and
- (
- (
- ((token=_STRING) or (idtoken=_SHORTSTRING)) and
- (cs_openstring in aktmoduleswitches) and
- not(cs_ansistrings in aktlocalswitches)
- ) or
- (idtoken=_OPENSTRING)) then
- begin
- consume(token);
- tt:=openshortstringtype;
- hs1:='openstring';
- inserthigh:=true;
- end
- else
- begin
- { everything else }
- single_type(tt,hs1,false);
- end;
- { default parameter }
- if (m_default_para in aktmodeswitches) then
- begin
- if try_to_consume(_EQUAL) then
- begin
- s:=sc.get(hpos);
- if not sc.empty then
- Comment(V_Error,'default value only allowed for one parameter');
- sc.add(s,hpos);
- { prefix 'def' to the parameter name }
- tdefaultvalue:=ReadConstant('$def'+Upper(s),hpos);
- if assigned(tdefaultvalue) then
- tprocdef(aktprocdef).parast.insert(tdefaultvalue);
- defaultrequired:=true;
- end
- else
- begin
- if defaultrequired then
- Comment(V_Error,'default parameter required');
- end;
- end;
- end;
- end
- else
- begin
- {$ifndef UseNiceNames}
- hs1:='$$$';
- {$else UseNiceNames}
- hs1:='var';
- {$endif UseNiceNames}
- tt:=cformaltype;
- end;
- storetokenpos:=akttokenpos;
- while not sc.empty do
- begin
- s:=sc.get(akttokenpos);
- { For proc vars we only need the definitions }
- if not is_procvar then
- begin
- vs:=tvarsym.create(s,tt);
- vs.varspez:=varspez;
- { we have to add this to avoid var param to be in registers !!!}
- { I don't understand the comment above, }
- { but I suppose the comment is wrong and }
- { it means that the address of var parameters can be placed }
- { in a register (FK) }
- if (varspez in [vs_var,vs_const,vs_out]) and
- paramanager.push_addr_param(tt.def,false) then
- include(vs.varoptions,vo_regable);
- { insert the sym in the parasymtable }
- tprocdef(aktprocdef).parast.insert(vs);
- { do we need a local copy? Then rename the varsym, do this after the
- insert so the dup id checking is done correctly }
- if (varspez=vs_value) and
- paramanager.push_addr_param(tt.def,aktprocdef.proccalloption in [pocall_cdecl,pocall_cppdecl]) and
- not(is_open_array(tt.def) or is_array_of_const(tt.def)) then
- tprocdef(aktprocdef).parast.rename(vs.name,'val'+vs.name);
- { also need to push a high value? }
- if inserthigh then
- begin
- hvs:=tvarsym.create('$high'+Upper(s),s32bittype);
- hvs.varspez:=vs_const;
- tprocdef(aktprocdef).parast.insert(hvs);
- end;
- end
- else
- vs:=nil;
- aktprocdef.concatpara(tt,vs,varspez,tdefaultvalue);
- end;
- {$ifdef fixLeaksOnError}
- if PStringContainer(strContStack.pop) <> sc then
- writeln('problem with strContStack in pdecl (1)');
- {$endif fixLeaksOnError}
- sc.free;
- akttokenpos:=storetokenpos;
- end;
- { set the new mangled name }
- until not try_to_consume(_SEMICOLON);
- dec(testcurobject);
- current_object_option:=old_object_option;
- consume(_RKLAMMER);
- end;
- procedure parse_proc_head(options:tproctypeoption);
- var
- orgsp,sp:stringid;
- paramoffset:longint;
- sym:tsym;
- st : tsymtable;
- srsymtable : tsymtable;
- pdl : pprocdeflist;
- storepos,procstartfilepos : tfileposinfo;
- i: longint;
- begin
- { Save the position where this procedure really starts }
- procstartfilepos:=akttokenpos;
- aktprocdef:=nil;
- if (options=potype_operator) then
- begin
- sp:=overloaded_names[optoken];
- orgsp:=sp;
- end
- else
- begin
- sp:=pattern;
- orgsp:=orgpattern;
- consume(_ID);
- end;
- { examine interface map: function/procedure iname.functionname=locfuncname }
- if parse_only and
- assigned(procinfo._class) and
- assigned(procinfo._class.implementedinterfaces) and
- (procinfo._class.implementedinterfaces.count>0) and
- try_to_consume(_POINT) then
- begin
- storepos:=akttokenpos;
- akttokenpos:=procstartfilepos;
- { get interface syms}
- searchsym(sp,sym,srsymtable);
- if not assigned(sym) then
- begin
- identifier_not_found(orgsp);
- sym:=generrorsym;
- end;
- akttokenpos:=storepos;
- { load proc name }
- if sym.typ=typesym then
- i:=procinfo._class.implementedinterfaces.searchintf(ttypesym(sym).restype.def);
- { qualifier is interface name? }
- if (sym.typ<>typesym) or (ttypesym(sym).restype.def.deftype<>objectdef) or
- (i=-1) then
- begin
- Message(parser_e_interface_id_expected);
- aktprocsym:=nil;
- end
- else
- begin
- aktprocsym:=tprocsym(procinfo._class.implementedinterfaces.interfaces(i).symtable.search(sp));
- { the method can be declared after the mapping FK
- if not(assigned(aktprocsym)) then
- Message(parser_e_methode_id_expected);
- }
- end;
- consume(_ID);
- consume(_EQUAL);
- if (token=_ID) { and assigned(aktprocsym) } then
- procinfo._class.implementedinterfaces.addmappings(i,sp,pattern);
- consume(_ID);
- exit;
- end;
- { method ? }
- if not(parse_only) and
- (lexlevel=normal_function_level) and
- try_to_consume(_POINT) then
- begin
- { search for object name }
- storepos:=akttokenpos;
- akttokenpos:=procstartfilepos;
- searchsym(sp,sym,srsymtable);
- if not assigned(sym) then
- begin
- identifier_not_found(orgsp);
- sym:=generrorsym;
- end;
- akttokenpos:=storepos;
- { consume proc name }
- sp:=pattern;
- orgsp:=orgpattern;
- procstartfilepos:=akttokenpos;
- consume(_ID);
- { qualifier is class name ? }
- if (sym.typ<>typesym) or
- (ttypesym(sym).restype.def.deftype<>objectdef) then
- begin
- Message(parser_e_class_id_expected);
- aktprocsym:=nil;
- aktprocdef:=nil;
- end
- else
- begin
- { used to allow private syms to be seen }
- aktobjectdef:=tobjectdef(ttypesym(sym).restype.def);
- procinfo._class:=tobjectdef(ttypesym(sym).restype.def);
- aktprocsym:=tprocsym(procinfo._class.symtable.search(sp));
- {The procedure has been found. So it is
- a global one. Set the flags to mark this.}
- procinfo.flags:=procinfo.flags or pi_is_global;
- aktobjectdef:=nil;
- { we solve this below }
- if not(assigned(aktprocsym)) then
- Message(parser_e_methode_id_expected);
- end;
- end
- else
- begin
- { check for constructor/destructor which is not allowed here }
- if (not parse_only) and
- (options in [potype_constructor,potype_destructor]) then
- Message(parser_e_constructors_always_objects);
- akttokenpos:=procstartfilepos;
- aktprocsym:=tprocsym(symtablestack.search(sp));
- if not(parse_only) then
- begin
- {The procedure we prepare for is in the implementation
- part of the unit we compile. It is also possible that we
- are compiling a program, which is also some kind of
- implementaion part.
- We need to find out if the procedure is global. If it is
- global, it is in the global symtable.}
- if not assigned(aktprocsym) and
- (symtablestack.symtabletype=staticsymtable) and
- assigned(symtablestack.next) and
- (symtablestack.next.unitid=0) then
- begin
- {Search the procedure in the global symtable.}
- aktprocsym:=tprocsym(symtablestack.next.search(sp));
- if assigned(aktprocsym) then
- begin
- {Check if it is a procedure.}
- if aktprocsym.typ<>procsym then
- DuplicateSym(aktprocsym);
- {The procedure has been found. So it is
- a global one. Set the flags to mark this.}
- procinfo.flags:=procinfo.flags or pi_is_global;
- end;
- end;
- end;
- end;
- if assigned(aktprocsym) then
- begin
- { Check if overloaded is a procsym }
- if aktprocsym.typ<>procsym then
- begin
- { when the other symbol is a unit symbol then hide the unit
- symbol. Only in tp mode because it's bad programming }
- if (m_duplicate_names in aktmodeswitches) and
- (aktprocsym.typ=unitsym) then
- begin
- aktprocsym.owner.rename(aktprocsym.name,'hidden'+aktprocsym.name);
- end
- else
- begin
- { we use a different error message for tp7 so it looks more compatible }
- if (m_fpc in aktmodeswitches) then
- Message1(parser_e_overloaded_no_procedure,aktprocsym.realname)
- else
- DuplicateSym(aktprocsym);
- { rename the name to an unique name to avoid an
- error when inserting the symbol in the symtable }
- orgsp:=orgsp+'$'+tostr(aktfilepos.line);
- end;
- { generate a new aktprocsym }
- aktprocsym:=nil;
- end;
- end;
- { test again if assigned, it can be reset to recover }
- if not assigned(aktprocsym) then
- begin
- { create a new procsym and set the real filepos }
- akttokenpos:=procstartfilepos;
- { for operator we have only one procsym for each overloaded
- operation }
- if (options=potype_operator) then
- begin
- { is the current overload sym already in the current unit }
- if assigned(overloaded_operators[optoken]) and
- (overloaded_operators[optoken].owner=symtablestack) then
- aktprocsym:=overloaded_operators[optoken]
- else
- begin
- { create the procsym with saving the original case }
- aktprocsym:=tprocsym.create('$'+sp);
- if assigned(overloaded_operators[optoken]) then
- overloaded_operators[optoken].concat_procdefs_to(aktprocsym);
- end;
- end
- else
- aktprocsym:=tprocsym.create(orgsp);
- symtablestack.insert(aktprocsym);
- end;
- st:=symtablestack;
- aktprocdef:=tprocdef.create;
- aktprocdef.symtablelevel:=symtablestack.symtablelevel;
- if assigned(procinfo._class) then
- aktprocdef._class := procinfo._class;
- { set the options from the caller (podestructor or poconstructor) }
- aktprocdef.proctypeoption:=options;
- { add procsym to the procdef }
- aktprocdef.procsym:=aktprocsym;
- { save file position }
- aktprocdef.fileinfo:=procstartfilepos;
- { this must also be inserted in the right symtable !! PM }
- { otherwise we get subbtle problems with
- definitions of args defs in staticsymtable for
- implementation of a global method }
- if token=_LKLAMMER then
- parameter_dec(aktprocdef);
- { calculate the offset of the parameters }
- paramoffset:=target_info.first_parm_offset;
- { calculate frame pointer offset }
- if lexlevel>normal_function_level then
- begin
- procinfo.framepointer_offset:=paramoffset;
- inc(paramoffset,pointer_size);
- { this is needed to get correct framepointer push for local
- forward functions !! }
- aktprocdef.parast.symtablelevel:=lexlevel;
- end;
- if assigned (procinfo._Class) and
- is_object(procinfo._Class) and
- (aktprocdef.proctypeoption in [potype_constructor,potype_destructor]) then
- inc(paramoffset,pointer_size);
- { self pointer offset, must be done after parsing the parameters }
- { self isn't pushed in nested procedure of methods }
- if assigned(procinfo._class) and (lexlevel=normal_function_level) then
- begin
- procinfo.selfpointer_offset:=paramoffset;
- if assigned(aktprocdef) and
- not(po_containsself in aktprocdef.procoptions) then
- inc(paramoffset,pointer_size);
- end;
- { con/-destructor flag ? }
- if assigned (procinfo._Class) and
- is_class(procinfo._class) and
- (aktprocdef.proctypeoption in [potype_destructor,potype_constructor]) then
- inc(paramoffset,pointer_size);
- procinfo.para_offset:=paramoffset;
- { so we only restore the symtable now }
- symtablestack:=st;
- if (options=potype_operator) then
- overloaded_operators[optoken]:=aktprocsym;
- end;
- procedure parse_proc_dec;
- var
- hs : string;
- isclassmethod : boolean;
- begin
- inc(lexlevel);
- { read class method }
- if token=_CLASS then
- begin
- consume(_CLASS);
- isclassmethod:=true;
- end
- else
- isclassmethod:=false;
- case token of
- _FUNCTION : begin
- consume(_FUNCTION);
- parse_proc_head(potype_none);
- if token<>_COLON then
- begin
- if assigned(aktprocsym) and
- not(is_interface(aktprocdef._class)) and
- not(aktprocdef.forwarddef) or
- (m_repeat_forward in aktmodeswitches) then
- begin
- consume(_COLON);
- consume_all_until(_SEMICOLON);
- end;
- end
- else
- begin
- consume(_COLON);
- inc(testcurobject);
- single_type(aktprocdef.rettype,hs,false);
- aktprocdef.test_if_fpu_result;
- dec(testcurobject);
- end;
- end;
- _PROCEDURE : begin
- consume(_PROCEDURE);
- parse_proc_head(potype_none);
- if assigned(aktprocsym) then
- aktprocdef.rettype:=voidtype;
- end;
- _CONSTRUCTOR : begin
- consume(_CONSTRUCTOR);
- parse_proc_head(potype_constructor);
- if assigned(procinfo._class) and
- is_class(procinfo._class) then
- begin
- { CLASS constructors return the created instance }
- aktprocdef.rettype.setdef(procinfo._class);
- end
- else
- begin
- { OBJECT constructors return a boolean }
- aktprocdef.rettype:=booltype;
- end;
- end;
- _DESTRUCTOR : begin
- consume(_DESTRUCTOR);
- parse_proc_head(potype_destructor);
- aktprocdef.rettype:=voidtype;
- end;
- _OPERATOR : begin
- if lexlevel>normal_function_level then
- Message(parser_e_no_local_operator);
- consume(_OPERATOR);
- if (token in [first_overloaded..last_overloaded]) then
- begin
- procinfo.flags:=procinfo.flags or pi_operator;
- optoken:=token;
- end
- else
- begin
- Message(parser_e_overload_operator_failed);
- { Use the dummy NOTOKEN that is also declared
- for the overloaded_operator[] }
- optoken:=NOTOKEN;
- end;
- consume(Token);
- parse_proc_head(potype_operator);
- if token<>_ID then
- begin
- otsym:=nil;
- if not(m_result in aktmodeswitches) then
- consume(_ID);
- end
- else
- begin
- otsym:=tvarsym.create(pattern,voidtype);
- consume(_ID);
- end;
- if not try_to_consume(_COLON) then
- begin
- consume(_COLON);
- aktprocdef.rettype:=generrortype;
- consume_all_until(_SEMICOLON);
- end
- else
- begin
- single_type(aktprocdef.rettype,hs,false);
- aktprocdef.test_if_fpu_result;
- if (optoken in [_EQUAL,_GT,_LT,_GTE,_LTE]) and
- ((aktprocdef.rettype.def.deftype<>
- orddef) or (torddef(aktprocdef.
- rettype.def).typ<>bool8bit)) then
- Message(parser_e_comparative_operator_return_boolean);
- if assigned(otsym) then
- otsym.vartype.def:=aktprocdef.rettype.def;
- if (optoken=_ASSIGNMENT) and
- is_equal(aktprocdef.rettype.def,
- tvarsym(aktprocdef.parast.symindex.first).vartype.def) then
- message(parser_e_no_such_assignment)
- else if not isoperatoracceptable(aktprocdef,optoken) then
- Message(parser_e_overload_impossible);
- end;
- end;
- end;
- if isclassmethod and
- assigned(aktprocsym) then
- include(aktprocdef.procoptions,po_classmethod);
- { support procedure proc;stdcall export; in Delphi mode only }
- if not((m_delphi in aktmodeswitches) and
- is_proc_directive(token)) then
- consume(_SEMICOLON);
- dec(lexlevel);
- end;
- {****************************************************************************
- Procedure directive handlers
- ****************************************************************************}
- procedure pd_far;
- begin
- Message(parser_w_proc_far_ignored);
- end;
- procedure pd_near;
- begin
- Message(parser_w_proc_near_ignored);
- end;
- procedure pd_export;
- begin
- if assigned(procinfo._class) then
- Message(parser_e_methods_dont_be_export);
- if lexlevel<>normal_function_level then
- Message(parser_e_dont_nest_export);
- { only os/2 needs this }
- if target_info.system=system_i386_os2 then
- begin
- aktprocdef.aliasnames.insert(aktprocsym.realname);
- procinfo.exported:=true;
- if cs_link_deffile in aktglobalswitches then
- deffile.AddExport(aktprocdef.mangledname);
- end;
- end;
- procedure pd_forward;
- begin
- aktprocdef.forwarddef:=true;
- end;
- procedure pd_alias;
- begin
- consume(_COLON);
- aktprocdef.aliasnames.insert(get_stringconst);
- end;
- procedure pd_asmname;
- begin
- aktprocdef.setmangledname(target_info.Cprefix+pattern);
- aktprocdef.has_mangledname:=true;
- if token=_CCHAR then
- consume(_CCHAR)
- else
- consume(_CSTRING);
- { we don't need anything else }
- aktprocdef.forwarddef:=false;
- end;
- procedure pd_intern;
- begin
- consume(_COLON);
- aktprocdef.extnumber:=get_intconst;
- end;
- procedure pd_interrupt;
- begin
- if lexlevel<>normal_function_level then
- Message(parser_e_dont_nest_interrupt);
- end;
- procedure pd_abstract;
- begin
- if (po_virtualmethod in aktprocdef.procoptions) then
- include(aktprocdef.procoptions,po_abstractmethod)
- else
- Message(parser_e_only_virtual_methods_abstract);
- { the method is defined }
- aktprocdef.forwarddef:=false;
- end;
- procedure pd_virtual;
- {$ifdef WITHDMT}
- var
- pt : tnode;
- {$endif WITHDMT}
- begin
- if (aktprocdef.proctypeoption=potype_constructor) and
- is_object(aktprocdef._class) then
- Message(parser_e_constructor_cannot_be_not_virtual);
- {$ifdef WITHDMT}
- if is_object(aktprocdef._class) and
- (token<>_SEMICOLON) then
- begin
- { any type of parameter is allowed here! }
- pt:=comp_expr(true);
- if is_constintnode(pt) then
- begin
- include(aktprocdef.procoptions,po_msgint);
- aktprocdef.messageinf.i:=pt^.value;
- end
- else
- Message(parser_e_ill_msg_expr);
- disposetree(pt);
- end;
- {$endif WITHDMT}
- end;
- procedure pd_static;
- begin
- if (cs_static_keyword in aktmoduleswitches) then
- begin
- include(aktprocsym.symoptions,sp_static);
- include(aktprocdef.procoptions,po_staticmethod);
- end;
- end;
- procedure pd_override;
- begin
- if not(is_class_or_interface(aktprocdef._class)) then
- Message(parser_e_no_object_override);
- end;
- procedure pd_overload;
- begin
- include(aktprocsym.symoptions,sp_has_overloaded);
- end;
- procedure pd_message;
- var
- pt : tnode;
- begin
- { check parameter type }
- if not(po_containsself in aktprocdef.procoptions) and
- ((aktprocdef.minparacount<>1) or
- (aktprocdef.maxparacount<>1) or
- (TParaItem(aktprocdef.Para.first).paratyp<>vs_var)) then
- Message(parser_e_ill_msg_param);
- pt:=comp_expr(true);
- if pt.nodetype=stringconstn then
- begin
- include(aktprocdef.procoptions,po_msgstr);
- aktprocdef.messageinf.str:=strnew(tstringconstnode(pt).value_str);
- end
- else
- if is_constintnode(pt) then
- begin
- include(aktprocdef.procoptions,po_msgint);
- aktprocdef.messageinf.i:=tordconstnode(pt).value;
- end
- else
- Message(parser_e_ill_msg_expr);
- pt.free;
- end;
- procedure pd_reintroduce;
- begin
- Message1(parser_w_proc_directive_ignored,'REINTRODUCE');
- end;
- procedure pd_syscall;
- begin
- aktprocdef.forwarddef:=false;
- aktprocdef.extnumber:=get_intconst;
- end;
- procedure pd_external;
- {
- If import_dll=nil the procedure is assumed to be in another
- object file. In that object file it should have the name to
- which import_name is pointing to. Otherwise, the procedure is
- assumed to be in the DLL to which import_dll is pointing to. In
- that case either import_nr<>0 or import_name<>nil is true, so
- the procedure is either imported by number or by name. (DM)
- }
- var
- import_dll,
- import_name : string;
- import_nr : word;
- begin
- aktprocdef.forwarddef:=false;
- { forbid local external procedures }
- if lexlevel>normal_function_level then
- Message(parser_e_no_local_external);
- { If the procedure should be imported from a DLL, a constant string follows.
- This isn't really correct, an contant string expression follows
- so we check if an semicolon follows, else a string constant have to
- follow (FK) }
- import_nr:=0;
- import_name:='';
- if not(token=_SEMICOLON) and not(idtoken=_NAME) then
- begin
- import_dll:=get_stringconst;
- if (idtoken=_NAME) then
- begin
- consume(_NAME);
- import_name:=get_stringconst;
- end;
- if (idtoken=_INDEX) then
- begin
- {After the word index follows the index number in the DLL.}
- consume(_INDEX);
- import_nr:=get_intconst;
- end;
- { default is to used the realname of the procedure }
- if (import_nr=0) and (import_name='') then
- import_name:=aktprocsym.realname;
- { create importlib if not already done }
- if not(current_module.uses_imports) then
- begin
- current_module.uses_imports:=true;
- importlib.preparelib(current_module.modulename^);
- end;
- {$ifdef notused}
- if not(m_repeat_forward in aktmodeswitches) and
- { if the procedure is declared with the overload option }
- { it requires a full declaration in the implementation part }
- not(sp_has_overloaded in aktprocsym.symoptions) then
- begin
- { we can only have one overloaded here ! }
- if assigned(aktprocdef.defs.next) then
- importlib.importprocedure(aktprocdef.defs.next.mangledname,
- import_dll,import_nr,import_name)
- else
- importlib.importprocedure(aktprocdef.mangledname,import_dll,import_nr,import_name);
- end
- else
- {$endif notused}
- importlib.importprocedure(aktprocdef.mangledname,import_dll,import_nr,import_name);
- end
- else
- begin
- if (idtoken=_NAME) then
- begin
- consume(_NAME);
- import_name:=get_stringconst;
- aktprocdef.setmangledname(import_name);
- aktprocdef.has_mangledname:=true;
- end;
- end;
- end;
- type
- pd_handler=procedure;
- proc_dir_rec=record
- idtok : ttoken;
- pd_flags : longint;
- handler : pd_handler;
- pocall : tproccalloption;
- pooption : tprocoptions;
- mutexclpocall : tproccalloptions;
- mutexclpotype : tproctypeoptions;
- mutexclpo : tprocoptions;
- end;
- const
- {Should contain the number of procedure directives we support.}
- num_proc_directives=36;
- proc_direcdata:array[1..num_proc_directives] of proc_dir_rec=
- (
- (
- idtok:_ABSTRACT;
- pd_flags : pd_interface+pd_object+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_abstract;
- pocall : pocall_none;
- pooption : [po_abstractmethod];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [potype_constructor,potype_destructor];
- mutexclpo : [po_exports,po_interrupt,po_external]
- ),(
- idtok:_ALIAS;
- pd_flags : pd_implemen+pd_body+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_alias;
- pocall : pocall_none;
- pooption : [];
- mutexclpocall : [pocall_inline];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_ASMNAME;
- pd_flags : pd_interface+pd_implemen+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_asmname;
- pocall : pocall_cdecl;
- pooption : [po_external];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_ASSEMBLER;
- pd_flags : pd_implemen+pd_body+pd_notobjintf;
- handler : nil;
- pocall : pocall_none;
- pooption : [po_assembler];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_CDECL;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_cdecl;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_assembler,po_external]
- ),(
- idtok:_DYNAMIC;
- pd_flags : pd_interface+pd_object+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_virtual;
- pocall : pocall_none;
- pooption : [po_virtualmethod];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [];
- mutexclpo : [po_exports,po_interrupt,po_external]
- ),(
- idtok:_EXPORT;
- pd_flags : pd_body+pd_global+pd_interface+pd_implemen{??}+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_export;
- pocall : pocall_none;
- pooption : [po_exports];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [];
- mutexclpo : [po_external,po_interrupt]
- ),(
- idtok:_EXTERNAL;
- pd_flags : pd_implemen+pd_interface+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_external;
- pocall : pocall_none;
- pooption : [po_external];
- mutexclpocall : [pocall_internproc,pocall_inline,pocall_palmossyscall];
- mutexclpotype : [];
- mutexclpo : [po_exports,po_interrupt,po_assembler]
- ),(
- idtok:_FAR;
- pd_flags : pd_implemen+pd_body+pd_interface+pd_procvar+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_far;
- pocall : pocall_none;
- pooption : [];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [];
- mutexclpo : []
- ),(
- idtok:_FAR16;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_far16;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external,po_leftright]
- ),(
- idtok:_FORWARD;
- pd_flags : pd_implemen+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_forward;
- pocall : pocall_none;
- pooption : [];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_FPCCALL;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_fpccall;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_leftright]
- ),(
- idtok:_INLINE;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_notobjintf;
- handler : nil;
- pocall : pocall_inline;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [potype_constructor,potype_destructor];
- mutexclpo : [po_exports,po_external,po_interrupt]
- ),(
- idtok:_INTERNCONST;
- pd_flags : pd_implemen+pd_body+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_intern;
- pocall : pocall_none;
- pooption : [po_internconst];
- mutexclpocall : [];
- mutexclpotype : [potype_operator];
- mutexclpo : []
- ),(
- idtok:_INTERNPROC;
- pd_flags : pd_implemen+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_intern;
- pocall : pocall_internproc;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [potype_constructor,potype_destructor,potype_operator];
- mutexclpo : [po_exports,po_external,po_interrupt,po_assembler,po_iocheck,po_leftright]
- ),(
- idtok:_INTERRUPT;
- pd_flags : pd_implemen+pd_body+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_interrupt;
- pocall : pocall_none;
- pooption : [po_interrupt];
- mutexclpocall : [pocall_internproc,pocall_cdecl,pocall_cppdecl,
- pocall_inline,pocall_pascal,pocall_system,pocall_far16,pocall_fpccall];
- mutexclpotype : [potype_constructor,potype_destructor,potype_operator];
- mutexclpo : [po_external,po_leftright,po_clearstack]
- ),(
- idtok:_IOCHECK;
- pd_flags : pd_implemen+pd_body+pd_notobjintf;
- handler : nil;
- pocall : pocall_none;
- pooption : [po_iocheck];
- mutexclpocall : [pocall_internproc];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_MESSAGE;
- pd_flags : pd_interface+pd_object+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_message;
- pocall : pocall_none;
- pooption : []; { can be po_msgstr or po_msgint }
- mutexclpocall : [pocall_inline,pocall_internproc];
- mutexclpotype : [potype_constructor,potype_destructor,potype_operator];
- mutexclpo : [po_interrupt,po_external]
- ),(
- idtok:_NEAR;
- pd_flags : pd_implemen+pd_body+pd_procvar+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_near;
- pocall : pocall_none;
- pooption : [];
- mutexclpocall : [pocall_internproc];
- mutexclpotype : [];
- mutexclpo : []
- ),(
- idtok:_OVERLOAD;
- pd_flags : pd_implemen+pd_interface+pd_body;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_overload;
- pocall : pocall_none;
- pooption : [po_overload];
- mutexclpocall : [pocall_internproc];
- mutexclpotype : [];
- mutexclpo : []
- ),(
- idtok:_OVERRIDE;
- pd_flags : pd_interface+pd_object+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_override;
- pocall : pocall_none;
- pooption : [po_overridingmethod,po_virtualmethod];
- mutexclpocall : [pocall_inline,pocall_internproc];
- mutexclpotype : [];
- mutexclpo : [po_exports,po_external,po_interrupt]
- ),(
- idtok:_PASCAL;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_pascal;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_POPSTACK;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_none;
- pooption : [po_clearstack];
- mutexclpocall : [pocall_inline,pocall_internproc,pocall_stdcall];
- mutexclpotype : [];
- mutexclpo : [po_assembler,po_external]
- ),(
- idtok:_PUBLIC;
- pd_flags : pd_implemen+pd_body+pd_global+pd_notobject+pd_notobjintf;
- handler : nil;
- pocall : pocall_none;
- pooption : [];
- mutexclpocall : [pocall_internproc,pocall_inline];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_REGISTER;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_register;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_REINTRODUCE;
- pd_flags : pd_interface+pd_object;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_reintroduce;
- pocall : pocall_none;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : []
- ),(
- idtok:_SAFECALL;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_safecall;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_SAVEREGISTERS;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar+pd_notobjintf;
- handler : nil;
- pocall : pocall_none;
- pooption : [po_saveregisters];
- mutexclpocall : [pocall_internproc];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_STATIC;
- pd_flags : pd_interface+pd_object+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_static;
- pocall : pocall_none;
- pooption : [po_staticmethod];
- mutexclpocall : [pocall_inline,pocall_internproc];
- mutexclpotype : [potype_constructor,potype_destructor];
- mutexclpo : [po_external,po_interrupt,po_exports]
- ),(
- idtok:_STDCALL;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_stdcall;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external]
- ),(
- idtok:_SYSCALL;
- pd_flags : pd_interface+pd_implemen+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_syscall;
- pocall : pocall_palmossyscall;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external,po_assembler,po_interrupt,po_exports]
- ),(
- idtok:_SYSTEM;
- pd_flags : pd_implemen+pd_notobjintf;
- handler : nil;
- pocall : pocall_system;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_external,po_assembler,po_interrupt]
- ),(
- idtok:_VIRTUAL;
- pd_flags : pd_interface+pd_object+pd_notobjintf;
- handler : {$ifdef FPCPROCVAR}@{$endif}pd_virtual;
- pocall : pocall_none;
- pooption : [po_virtualmethod];
- mutexclpocall : [pocall_inline,pocall_internproc];
- mutexclpotype : [];
- mutexclpo : [po_external,po_interrupt,po_exports]
- ),(
- idtok:_CPPDECL;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_procvar;
- handler : nil;
- pocall : pocall_cppdecl;
- pooption : [po_savestdregs];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_assembler,po_external]
- ),(
- idtok:_VARARGS;
- pd_flags : pd_interface+pd_implemen+pd_procvar;
- handler : nil;
- pocall : pocall_none;
- pooption : [po_varargs];
- mutexclpocall : [pocall_internproc,pocall_stdcall,pocall_register,
- pocall_inline,pocall_far16,pocall_fpccall];
- mutexclpotype : [];
- mutexclpo : [po_assembler,po_interrupt,po_leftright]
- ),(
- idtok:_COMPILERPROC;
- pd_flags : pd_interface+pd_implemen+pd_body+pd_notobjintf;
- handler : nil;
- pocall : pocall_compilerproc;
- pooption : [];
- mutexclpocall : [];
- mutexclpotype : [];
- mutexclpo : [po_interrupt]
- )
- );
- function is_proc_directive(tok:ttoken):boolean;
- var
- i : longint;
- begin
- is_proc_directive:=false;
- for i:=1 to num_proc_directives do
- if proc_direcdata[i].idtok=idtoken then
- begin
- is_proc_directive:=true;
- exit;
- end;
- end;
- function parse_proc_direc(var pdflags:word):boolean;
- {
- Parse the procedure directive, returns true if a correct directive is found
- }
- var
- p : longint;
- found : boolean;
- name : stringid;
- begin
- parse_proc_direc:=false;
- name:=tokeninfo^[idtoken].str;
- found:=false;
- { Hint directive? Then exit immediatly }
- if (m_hintdirective in aktmodeswitches) then
- begin
- case idtoken of
- _LIBRARY,
- _PLATFORM,
- _DEPRECATED :
- exit;
- end;
- end;
- { retrieve data for directive if found }
- for p:=1 to num_proc_directives do
- if proc_direcdata[p].idtok=idtoken then
- begin
- found:=true;
- break;
- end;
- { Check if the procedure directive is known }
- if not found then
- begin
- { parsing a procvar type the name can be any
- next variable !! }
- if (pdflags and (pd_procvar or pd_object))=0 then
- Message1(parser_w_unknown_proc_directive_ignored,name);
- exit;
- end;
- { static needs a special treatment }
- if (idtoken=_STATIC) and not (cs_static_keyword in aktmoduleswitches) then
- exit;
- { Conflicts between directives ? }
- if (aktprocdef.proctypeoption in proc_direcdata[p].mutexclpotype) or
- (aktprocdef.proccalloption in proc_direcdata[p].mutexclpocall) or
- ((aktprocdef.procoptions*proc_direcdata[p].mutexclpo)<>[]) then
- begin
- Message1(parser_e_proc_dir_conflict,name);
- exit;
- end;
- { set calling convention }
- if proc_direcdata[p].pocall<>pocall_none then
- begin
- if aktprocdef.proccalloption<>pocall_none then
- begin
- Message2(parser_w_proc_overriding_calling,
- proccalloptionStr[aktprocdef.proccalloption],
- proccalloptionStr[proc_direcdata[p].pocall]);
- end;
- aktprocdef.proccalloption:=proc_direcdata[p].pocall;
- end;
- if aktprocdef.deftype=procdef then
- begin
- { Check if the directive is only for objects }
- if ((proc_direcdata[p].pd_flags and pd_object)<>0) and
- not assigned(aktprocdef._class) then
- exit;
- { check if method and directive not for object public }
- if ((proc_direcdata[p].pd_flags and pd_notobject)<>0) and
- assigned(aktprocdef._class) then
- exit;
- { check if method and directive not for interface }
- if ((proc_direcdata[p].pd_flags and pd_notobjintf)<>0) and
- is_interface(aktprocdef._class) then
- exit;
- end;
- { consume directive, and turn flag on }
- consume(token);
- parse_proc_direc:=true;
- { Check the pd_flags if the directive should be allowed }
- if ((pdflags and pd_interface)<>0) and
- ((proc_direcdata[p].pd_flags and pd_interface)=0) then
- begin
- Message1(parser_e_proc_dir_not_allowed_in_interface,name);
- exit;
- end;
- if ((pdflags and pd_implemen)<>0) and
- ((proc_direcdata[p].pd_flags and pd_implemen)=0) then
- begin
- Message1(parser_e_proc_dir_not_allowed_in_implementation,name);
- exit;
- end;
- if ((pdflags and pd_procvar)<>0) and
- ((proc_direcdata[p].pd_flags and pd_procvar)=0) then
- begin
- Message1(parser_e_proc_dir_not_allowed_in_procvar,name);
- exit;
- end;
- { Return the new pd_flags }
- if (proc_direcdata[p].pd_flags and pd_body)=0 then
- pdflags:=pdflags and (not pd_body);
- if (proc_direcdata[p].pd_flags and pd_global)<>0 then
- pdflags:=pdflags or pd_global;
- { Add the correct flag }
- aktprocdef.procoptions:=aktprocdef.procoptions+proc_direcdata[p].pooption;
- { Call the handler }
- if pointer({$ifndef FPCPROCVAR}@{$endif}proc_direcdata[p].handler)<>nil then
- proc_direcdata[p].handler{$ifdef FPCPROCVAR}(){$endif};
- end;
- procedure handle_calling_convention(sym:tprocsym;def:tabstractprocdef);
- begin
- { set the default calling convention }
- if def.proccalloption=pocall_none then
- def.proccalloption:=aktdefproccall;
- case def.proccalloption of
- pocall_cdecl :
- begin
- { use popstack and save std registers }
- include(def.procoptions,po_clearstack);
- include(def.procoptions,po_savestdregs);
- { set mangledname }
- if (def.deftype=procdef) then
- begin
- if not tprocdef(def).has_mangledname then
- begin
- if assigned(tprocdef(def)._class) then
- tprocdef(def).setmangledname(target_info.Cprefix+tprocdef(def)._class.objrealname^+'_'+sym.realname)
- else
- tprocdef(def).setmangledname(target_info.Cprefix+sym.realname);
- end;
- if not assigned(tprocdef(def).parast) then
- internalerror(200110234);
- { do not copy on local !! }
- tprocdef(def).parast.foreach_static({$ifdef FPCPROCVAR}@{$endif}resetvaluepara,nil);
- { Adjust alignment to match cdecl or stdcall }
- tprocdef(def).parast.dataalignment:=std_param_align;
- end;
- end;
- pocall_cppdecl :
- begin
- if not assigned(sym) then
- internalerror(200110231);
- { use popstack and save std registers }
- include(def.procoptions,po_clearstack);
- include(def.procoptions,po_savestdregs);
- { set mangledname }
- if (def.deftype=procdef) then
- begin
- if not tprocdef(def).has_mangledname then
- tprocdef(def).setmangledname(target_info.Cprefix+tprocdef(def).cplusplusmangledname);
- if not assigned(tprocdef(def).parast) then
- internalerror(200110235);
- { do not copy on local !! }
- tprocdef(def).parast.foreach_static({$ifdef FPCPROCVAR}@{$endif}resetvaluepara,nil);
- { Adjust alignment to match cdecl or stdcall }
- tprocdef(def).parast.dataalignment:=std_param_align;
- end;
- end;
- pocall_stdcall :
- begin
- include(def.procoptions,po_savestdregs);
- if (def.deftype=procdef) then
- begin
- if not assigned(tprocdef(def).parast) then
- internalerror(200110236);
- { Adjust alignment to match cdecl or stdcall }
- tprocdef(def).parast.dataalignment:=std_param_align;
- end;
- end;
- pocall_safecall :
- begin
- include(def.procoptions,po_savestdregs);
- end;
- pocall_compilerproc :
- begin
- if (not assigned(sym)) or
- (def.deftype<>procdef) then
- internalerror(200110232);
- tprocdef(def).setmangledname(lower(sym.name));
- end;
- pocall_pascal :
- begin
- include(def.procoptions,po_leftright);
- end;
- pocall_register :
- begin
- Message1(parser_w_proc_directive_ignored,'REGISTER');
- end;
- pocall_far16 :
- begin
- { Temporary stub, must be rewritten to support OS/2 far16 }
- Message1(parser_w_proc_directive_ignored,'FAR16');
- end;
- pocall_system :
- begin
- include(def.procoptions,po_clearstack);
- if (not assigned(sym)) or
- (def.deftype<>procdef) then
- internalerror(200110233);
- if not tprocdef(def).has_mangledname then
- tprocdef(def).setmangledname(sym.realname);
- end;
- pocall_palmossyscall :
- begin
- { use popstack and save std registers }
- include(def.procoptions,po_clearstack);
- include(def.procoptions,po_savestdregs);
- if (def.deftype=procdef) then
- begin
- if not assigned(tprocdef(def).parast) then
- internalerror(200110236);
- { do not copy on local !! }
- tprocdef(def).parast.foreach_static({$ifdef FPCPROCVAR}@{$endif}resetvaluepara,nil);
- { Adjust positions of args for cdecl or stdcall }
- tprocdef(def).parast.dataalignment:=std_param_align;
- end;
- end;
- pocall_inline :
- begin
- if not(cs_support_inline in aktmoduleswitches) then
- begin
- Message(parser_e_proc_inline_not_supported);
- def.proccalloption:=pocall_fpccall;
- end;
- end;
- end;
- { add mangledname to external list }
- if (def.deftype=procdef) and
- (po_external in def.procoptions) and
- target_info.DllScanSupported then
- current_module.externals.insert(tExternalsItem.create(tprocdef(def).mangledname));
- end;
- procedure calc_parasymtable_addresses(def:tprocdef);
- var
- lastps,
- highps,ps : tsym;
- st : tsymtable;
- begin
- st:=def.parast;
- if po_leftright in def.procoptions then
- begin
- { pushed in reversed order, left to right }
- highps:=nil;
- lastps:=nil;
- while assigned(st.symindex.first) and (lastps<>tsym(st.symindex.first)) do
- begin
- ps:=tsym(st.symindex.first);
- while assigned(ps.indexnext) and (tsym(ps.indexnext)<>lastps) do
- ps:=tsym(ps.indexnext);
- if ps.typ=varsym then
- begin
- { Wait with inserting the high value, it needs to be inserted
- after the corresponding parameter }
- if Copy(ps.name,1,4)='high' then
- highps:=ps
- else
- begin
- st.insertvardata(ps);
- { add also the high tree if it was saved }
- if assigned(highps) then
- begin
- st.insertvardata(highps);
- highps:=nil;
- end;
- end;
- end;
- lastps:=ps;
- end;
- if assigned(highps) then
- internalerror(200208257);
- end
- else
- begin
- { pushed in normal order, right to left }
- ps:=tsym(st.symindex.first);
- while assigned(ps) do
- begin
- if ps.typ=varsym then
- st.insertvardata(ps);
- ps:=tsym(ps.indexnext);
- end;
- end;
- end;
- procedure parse_proc_directives(var pdflags:word);
- {
- Parse the procedure directives. It does not matter if procedure directives
- are written using ;procdir; or ['procdir'] syntax.
- }
- var
- res : boolean;
- begin
- while token in [_ID,_LECKKLAMMER] do
- begin
- if try_to_consume(_LECKKLAMMER) then
- begin
- repeat
- parse_proc_direc(pdflags);
- until not try_to_consume(_COMMA);
- consume(_RECKKLAMMER);
- { we always expect at least '[];' }
- res:=true;
- end
- else
- begin
- res:=parse_proc_direc(pdflags);
- end;
- { A procedure directive normally followed by a semicolon, but in
- a const section we should stop when _EQUAL is found }
- if res then
- begin
- if (block_type=bt_const) and
- (token=_EQUAL) then
- break;
- { support procedure proc;stdcall export; in Delphi mode only }
- if not((m_delphi in aktmodeswitches) and
- is_proc_directive(token)) then
- consume(_SEMICOLON);
- end
- else
- break;
- end;
- handle_calling_convention(aktprocsym,aktprocdef);
- { calculate addresses in parasymtable }
- if aktprocdef.deftype=procdef then
- calc_parasymtable_addresses(aktprocdef);
- end;
- procedure parse_var_proc_directives(var sym : tsym);
- var
- pdflags : word;
- oldsym : tprocsym;
- olddef : tprocdef;
- pd : tabstractprocdef;
- begin
- oldsym:=aktprocsym;
- olddef:=aktprocdef;
- pdflags:=pd_procvar;
- { we create a temporary aktprocsym to read the directives }
- aktprocsym:=tprocsym.create(sym.name);
- case sym.typ of
- varsym :
- pd:=tabstractprocdef(tvarsym(sym).vartype.def);
- typedconstsym :
- pd:=tabstractprocdef(ttypedconstsym(sym).typedconsttype.def);
- typesym :
- pd:=tabstractprocdef(ttypesym(sym).restype.def);
- else
- internalerror(994932432);
- end;
- if pd.deftype<>procvardef then
- internalerror(994932433);
- tabstractprocdef(aktprocdef):=pd;
- { names should never be used anyway }
- inc(lexlevel);
- parse_proc_directives(pdflags);
- dec(lexlevel);
- aktprocsym.free;
- aktprocsym:=oldsym;
- aktprocdef:=olddef;
- end;
- procedure parse_object_proc_directives(var sym : tprocsym);
- var
- pdflags : word;
- begin
- pdflags:=pd_object;
- inc(lexlevel);
- parse_proc_directives(pdflags);
- dec(lexlevel);
- if (po_containsself in aktprocdef.procoptions) and
- (([po_msgstr,po_msgint]*aktprocdef.procoptions)=[]) then
- Message(parser_e_self_in_non_message_handler);
- end;
- function proc_add_definition(aprocsym:tprocsym;var aprocdef : tprocdef) : boolean;
- {
- Add definition aprocdef to the overloaded definitions of aprocsym. If a
- forwarddef is found and reused it returns true
- }
- var
- hd : tprocdef;
- ad,fd : tsym;
- forwardfound : boolean;
- i : cardinal;
- begin
- forwardfound:=false;
- { check overloaded functions if the same function already exists }
- for i:=1 to aprocsym.procdef_count do
- begin
- hd:=aprocsym.procdef[i];
- { check the parameters, for delphi/tp it is possible to
- leave the parameters away in the implementation (forwarddef=false).
- But for an overload declared function this is not allowed }
- if { check if empty implementation arguments match is allowed }
- (
- not(m_repeat_forward in aktmodeswitches) and
- not(aprocdef.forwarddef) and
- (aprocdef.maxparacount=0) and
- not(po_overload in hd.procoptions)
- ) or
- { check arguments }
- (
- equal_paras(aprocdef.para,hd.para,cp_none) and
- { for operators equal_paras is not enough !! }
- ((aprocdef.proctypeoption<>potype_operator) or (optoken<>_ASSIGNMENT) or
- is_equal(hd.rettype.def,aprocdef.rettype.def))
- ) then
- begin
- { Check if we've found the forwarddef, if found then
- we need to update the forward def with the current
- implementation settings }
- if hd.forwarddef then
- begin
- forwardfound:=true;
- { Check if the procedure type and return type are correct,
- also the parameters must match also with the type }
- if (hd.proctypeoption<>aprocdef.proctypeoption) or
- (
- (m_repeat_forward in aktmodeswitches) and
- (
- not(is_equal(hd.rettype.def,aprocdef.rettype.def) and
- ((aprocdef.maxparacount=0) or
- equal_paras(aprocdef.para,hd.para,cp_all))
- )
- )
- ) then
- begin
- MessagePos1(aprocdef.fileinfo,parser_e_header_dont_match_forward,
- aprocdef.fullprocname);
- break;
- end;
- { Check if both are declared forward }
- if hd.forwarddef and aprocdef.forwarddef then
- begin
- MessagePos1(aprocdef.fileinfo,parser_e_function_already_declared_public_forward,
- aprocdef.fullprocname);
- end;
- { internconst or internproc only need to be defined once }
- if (hd.proccalloption=pocall_internproc) then
- aprocdef.proccalloption:=hd.proccalloption
- else
- if (aprocdef.proccalloption=pocall_internproc) then
- hd.proccalloption:=aprocdef.proccalloption;
- if (po_internconst in hd.procoptions) then
- include(aprocdef.procoptions,po_internconst)
- else if (po_internconst in aprocdef.procoptions) then
- include(hd.procoptions,po_internconst);
- { Check calling convention }
- if (hd.proccalloption<>aprocdef.proccalloption) then
- begin
- { For delphi check if the current implementation has no proccalloption, then
- take the options from the interface }
- if not(m_delphi in aktmodeswitches) or
- (aprocdef.proccalloption<>pocall_none) then
- MessagePos(aprocdef.fileinfo,parser_e_call_convention_dont_match_forward);
- { restore interface settings }
- aprocdef.proccalloption:=hd.proccalloption;
- aprocdef.has_mangledname:=hd.has_mangledname;
- if hd.has_mangledname then
- aprocdef.setmangledname(hd.mangledname);
- end;
- { Check manglednames }
- if (m_repeat_forward in aktmodeswitches) or
- aprocdef.haspara then
- begin
- { If mangled names are equal then they have the same amount of arguments }
- { We can check the names of the arguments }
- { both symtables are in the same order from left to right }
- ad:=tsym(hd.parast.symindex.first);
- fd:=tsym(aprocdef.parast.symindex.first);
- repeat
- { skip default parameter constsyms }
- while assigned(ad) and (ad.typ<>varsym) do
- ad:=tsym(ad.indexnext);
- while assigned(fd) and (fd.typ<>varsym) do
- fd:=tsym(fd.indexnext);
- { stop when one of the two lists is at the end }
- if not assigned(ad) or not assigned(fd) then
- break;
- if (ad.name<>fd.name) then
- begin
- MessagePos3(aprocdef.fileinfo,parser_e_header_different_var_names,
- aprocsym.name,ad.name,fd.name);
- break;
- end;
- ad:=tsym(ad.indexnext);
- fd:=tsym(fd.indexnext);
- until false;
- if assigned(ad) or assigned(fd) then
- internalerror(200204178);
- end;
- { Everything is checked, now we can update the forward declaration
- with the new data from the implementation }
- hd.forwarddef:=aprocdef.forwarddef;
- hd.hasforward:=true;
- hd.parast.address_fixup:=aprocdef.parast.address_fixup;
- hd.procoptions:=hd.procoptions+aprocdef.procoptions;
- if hd.extnumber=65535 then
- hd.extnumber:=aprocdef.extnumber;
- while not aprocdef.aliasnames.empty do
- hd.aliasnames.insert(aprocdef.aliasnames.getfirst);
- { update mangledname if the implementation has a fixed mangledname set }
- if aprocdef.has_mangledname then
- begin
- { rename also asmsymbol first, because the name can already be used }
- objectlibrary.renameasmsymbol(hd.mangledname,aprocdef.mangledname);
- { update the mangledname }
- hd.has_mangledname:=true;
- hd.setmangledname(aprocdef.mangledname);
- end;
- { for compilerproc defines we need to rename and update the
- symbolname to lowercase }
- if (aprocdef.proccalloption=pocall_compilerproc) then
- begin
- { rename to lowercase so users can't access it }
- aprocsym.owner.rename(aprocsym.name,lower(aprocsym.name));
- { also update the realname that is stored in the ppu }
- stringdispose(aprocsym._realname);
- aprocsym._realname:=stringdup('$'+aprocsym.name);
- { the mangeled name is already changed by the pd_compilerproc }
- { handler. It must be done immediately because if we have a }
- { call to a compilerproc before it's implementation is }
- { encountered, it must already use the new mangled name (JM) }
- end;
- { return the forwarddef }
- aprocdef:=hd;
- end
- else
- begin
- { abstract methods aren't forward defined, but this }
- { needs another error message }
- if (po_abstractmethod in hd.procoptions) then
- MessagePos(aprocdef.fileinfo,parser_e_abstract_no_definition)
- else
- MessagePos(aprocdef.fileinfo,parser_e_overloaded_have_same_parameters);
- end;
- { we found one proc with the same arguments, there are no others
- so we can stop }
- break;
- end;
- { check for allowing overload directive }
- if not(m_fpc in aktmodeswitches) then
- begin
- { overload directive turns on overloading }
- if ((po_overload in aprocdef.procoptions) or
- (po_overload in hd.procoptions)) then
- begin
- { check if all procs have overloading, but not if the proc was
- already declared forward, then the check is already done }
- if not(hd.hasforward or
- (aprocdef.forwarddef<>hd.forwarddef) or
- ((po_overload in aprocdef.procoptions) and
- (po_overload in hd.procoptions))) then
- begin
- MessagePos1(aprocdef.fileinfo,parser_e_no_overload_for_all_procs,aprocsym.realname);
- break;
- end;
- end
- else
- begin
- if not(hd.forwarddef) then
- begin
- MessagePos(aprocdef.fileinfo,parser_e_procedure_overloading_is_off);
- break;
- end;
- end;
- end; { equal arguments }
- end;
- { if we didn't reuse a forwarddef then we add the procdef to the overloaded
- list }
- if not forwardfound then
- begin
- aprocsym.addprocdef(aprocdef);
- { add overloadnumber for unique naming, the overloadcount is
- counted per module and 0 for the first procedure }
- aprocdef.overloadnumber:=aprocsym.overloadcount;
- inc(aprocsym.overloadcount);
- end;
- { insert otsym only in the right symtable }
- if ((procinfo.flags and pi_operator)<>0) and
- assigned(otsym) then
- begin
- if not parse_only then
- begin
- if paramanager.ret_in_param(aprocdef.rettype.def) then
- begin
- aprocdef.parast.insert(otsym);
- { this allows to read the funcretoffset }
- otsym.address:=-4;
- otsym.varspez:=vs_var;
- end
- else
- begin
- aprocdef.localst.insert(otsym);
- aprocdef.localst.insertvardata(otsym);
- end;
- end
- else
- begin
- { this is not required anymore }
- otsym.free;
- otsym:=nil;
- end;
- end;
- paramanager.create_param_loc_info(aprocdef);
- proc_add_definition:=forwardfound;
- end;
- end.
- {
- $Log$
- Revision 1.71 2002-09-07 15:25:06 peter
- * old logs removed and tabs fixed
- Revision 1.70 2002/09/03 16:26:27 daniel
- * Make Tprocdef.defs protected
- Revision 1.69 2002/09/01 12:11:33 peter
- * calc param_offset after parameters are read, because the calculation
- depends on po_containself
- Revision 1.68 2002/08/25 19:25:20 peter
- * sym.insert_in_data removed
- * symtable.insertvardata/insertconstdata added
- * removed insert_in_data call from symtable.insert, it needs to be
- called separatly. This allows to deref the address calculation
- * procedures now calculate the parast addresses after the procedure
- directives are parsed. This fixes the cdecl parast problem
- * push_addr_param has an extra argument that specifies if cdecl is used
- or not
- Revision 1.67 2002/08/25 11:33:06 peter
- * also check the paratypes when a forward was found
- Revision 1.66 2002/08/19 19:36:44 peter
- * More fixes for cross unit inlining, all tnodes are now implemented
- * Moved pocall_internconst to po_internconst because it is not a
- calling type at all and it conflicted when inlining of these small
- functions was requested
- Revision 1.65 2002/08/18 20:06:24 peter
- * inlining is now also allowed in interface
- * renamed write/load to ppuwrite/ppuload
- * tnode storing in ppu
- * nld,ncon,nbas are already updated for storing in ppu
- Revision 1.64 2002/08/17 09:23:39 florian
- * first part of procinfo rewrite
- Revision 1.63 2002/08/11 14:32:27 peter
- * renamed current_library to objectlibrary
- Revision 1.62 2002/08/11 13:24:12 peter
- * saving of asmsymbols in ppu supported
- * asmsymbollist global is removed and moved into a new class
- tasmlibrarydata that will hold the info of a .a file which
- corresponds with a single module. Added librarydata to tmodule
- to keep the library info stored for the module. In the future the
- objectfiles will also be stored to the tasmlibrarydata class
- * all getlabel/newasmsymbol and friends are moved to the new class
- Revision 1.61 2002/07/26 21:15:40 florian
- * rewrote the system handling
- Revision 1.60 2002/07/20 11:57:55 florian
- * types.pas renamed to defbase.pas because D6 contains a types
- unit so this would conflicts if D6 programms are compiled
- + Willamette/SSE2 instructions to assembler added
- Revision 1.59 2002/07/11 14:41:28 florian
- * start of the new generic parameter handling
- Revision 1.58 2002/07/01 18:46:25 peter
- * internal linker
- * reorganized aasm layer
- Revision 1.57 2002/05/18 13:34:12 peter
- * readded missing revisions
- Revision 1.56 2002/05/16 19:46:42 carl
- + defines.inc -> fpcdefs.inc to avoid conflicts if compiling by hand
- + try to fix temp allocation (still in ifdef)
- + generic constructor calls
- + start of tassembler / tmodulebase class cleanup
- Revision 1.54 2002/05/12 16:53:08 peter
- * moved entry and exitcode to ncgutil and cgobj
- * foreach gets extra argument for passing local data to the
- iterator function
- * -CR checks also class typecasts at runtime by changing them
- into as
- * fixed compiler to cycle with the -CR option
- * fixed stabs with elf writer, finally the global variables can
- be watched
- * removed a lot of routines from cga unit and replaced them by
- calls to cgobj
- * u32bit-s32bit updates for and,or,xor nodes. When one element is
- u32bit then the other is typecasted also to u32bit without giving
- a rangecheck warning/error.
- * fixed pascal calling method with reversing also the high tree in
- the parast, detected by tcalcst3 test
- Revision 1.53 2002/04/21 19:02:04 peter
- * removed newn and disposen nodes, the code is now directly
- inlined from pexpr
- * -an option that will write the secondpass nodes to the .s file, this
- requires EXTDEBUG define to actually write the info
- * fixed various internal errors and crashes due recent code changes
- Revision 1.52 2002/04/20 21:32:24 carl
- + generic FPC_CHECKPOINTER
- + first parameter offset in stack now portable
- * rename some constants
- + move some cpu stuff to other units
- - remove unused constents
- * fix stacksize for some targets
- * fix generic size problems which depend now on EXTEND_SIZE constant
- Revision 1.51 2002/04/20 15:27:05 carl
- - remove ifdef i386 define
- Revision 1.50 2002/04/19 15:46:02 peter
- * mangledname rewrite, tprocdef.mangledname is now created dynamicly
- in most cases and not written to the ppu
- * add mangeledname_prefix() routine to generate the prefix of
- manglednames depending on the current procedure, object and module
- * removed static procprefix since the mangledname is now build only
- on demand from tprocdef.mangledname
- }
|