1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495969798991001011021031041051061071081091101111121131141151161171181191201211221231241251261271281291301311321331341351361371381391401411421431441451461471481491501511521531541551561571581591601611621631641651661671681691701711721731741751761771781791801811821831841851861871881891901911921931941951961971981992002012022032042052062072082092102112122132142152162172182192202212222232242252262272282292302312322332342352362372382392402412422432442452462472482492502512522532542552562572582592602612622632642652662672682692702712722732742752762772782792802812822832842852862872882892902912922932942952962972982993003013023033043053063073083093103113123133143153163173183193203213223233243253263273283293303313323333343353363373383393403413423433443453463473483493503513523533543553563573583593603613623633643653663673683693703713723733743753763773783793803813823833843853863873883893903913923933943953963973983994004014024034044054064074084094104114124134144154164174184194204214224234244254264274284294304314324334344354364374384394404414424434444454464474484494504514524534544554564574584594604614624634644654664674684694704714724734744754764774784794804814824834844854864874884894904914924934944954964974984995005015025035045055065075085095105115125135145155165175185195205215225235245255265275285295305315325335345355365375385395405415425435445455465475485495505515525535545555565575585595605615625635645655665675685695705715725735745755765775785795805815825835845855865875885895905915925935945955965975985996006016026036046056066076086096106116126136146156166176186196206216226236246256266276286296306316326336346356366376386396406416426436446456466476486496506516526536546556566576586596606616626636646656666676686696706716726736746756766776786796806816826836846856866876886896906916926936946956966976986997007017027037047057067077087097107117127137147157167177187197207217227237247257267277287297307317327337347357367377387397407417427437447457467477487497507517527537547557567577587597607617627637647657667677687697707717727737747757767777787797807817827837847857867877887897907917927937947957967977987998008018028038048058068078088098108118128138148158168178188198208218228238248258268278288298308318328338348358368378388398408418428438448458468478488498508518528538548558568578588598608618628638648658668678688698708718728738748758768778788798808818828838848858868878888898908918928938948958968978988999009019029039049059069079089099109119129139149159169179189199209219229239249259269279289299309319329339349359369379389399409419429439449459469479489499509519529539549559569579589599609619629639649659669679689699709719729739749759769779789799809819829839849859869879889899909919929939949959969979989991000100110021003100410051006100710081009101010111012101310141015101610171018101910201021102210231024102510261027102810291030103110321033103410351036103710381039104010411042104310441045104610471048104910501051105210531054105510561057105810591060106110621063106410651066106710681069107010711072107310741075107610771078107910801081108210831084108510861087108810891090109110921093109410951096109710981099110011011102110311041105110611071108110911101111111211131114111511161117111811191120112111221123112411251126112711281129113011311132113311341135113611371138113911401141114211431144114511461147114811491150115111521153115411551156115711581159116011611162116311641165116611671168116911701171117211731174117511761177117811791180118111821183118411851186118711881189119011911192119311941195119611971198119912001201120212031204120512061207120812091210121112121213121412151216121712181219122012211222122312241225122612271228122912301231123212331234123512361237123812391240124112421243124412451246124712481249125012511252125312541255125612571258125912601261126212631264126512661267126812691270127112721273127412751276127712781279128012811282128312841285128612871288128912901291129212931294129512961297129812991300130113021303130413051306130713081309131013111312131313141315131613171318131913201321132213231324132513261327132813291330133113321333133413351336133713381339134013411342134313441345134613471348134913501351135213531354135513561357135813591360136113621363136413651366136713681369137013711372137313741375137613771378137913801381138213831384138513861387138813891390139113921393139413951396139713981399140014011402140314041405140614071408140914101411141214131414141514161417141814191420142114221423142414251426142714281429143014311432143314341435143614371438143914401441144214431444144514461447144814491450145114521453145414551456145714581459146014611462146314641465146614671468146914701471147214731474147514761477147814791480148114821483148414851486148714881489149014911492149314941495149614971498149915001501150215031504150515061507150815091510151115121513151415151516151715181519152015211522152315241525152615271528152915301531153215331534153515361537153815391540154115421543154415451546154715481549155015511552155315541555155615571558155915601561156215631564156515661567156815691570157115721573157415751576157715781579158015811582158315841585158615871588158915901591159215931594159515961597159815991600160116021603160416051606160716081609161016111612161316141615161616171618161916201621162216231624162516261627162816291630163116321633163416351636163716381639164016411642164316441645164616471648164916501651165216531654165516561657165816591660166116621663166416651666166716681669167016711672167316741675167616771678167916801681168216831684168516861687168816891690169116921693169416951696169716981699170017011702170317041705(*
Copyright (c) 2001-2002,
George C. Necula <necula@cs.berkeley.edu>
Scott McPeak <smcpeak@cs.berkeley.edu>
Wes Weimer <weimer@cs.berkeley.edu>
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are
met:
1. Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in the
documentation and/or other materials provided with the distribution.
3. The names of the contributors may not be used to endorse or promote
products derived from this software without specific prior written
permission.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS
IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A
PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER
OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*)(* mergecil.ml *)(* This module is responsible for merging multiple CIL source trees into
a single, coherent CIL tree which contains the union of all the
definitions in the source files. It effectively acts like a linker,
but at the source code level instead of the object code level. *)moduleP=PrettyopenCilmoduleE=ErrormsgmoduleH=HashtblmoduleA=AlphaopenTraceletdebugMerge=falseletdebugInlines=falseletignore_merge_conflicts=reffalse(* Try to merge structure with the same name. However, do not complain if
they are not the same *)letmergeSynonyms=true(** Whether to use path compression *)letusePathCompression=false(* Try to merge definitions of inline functions. They can appear in multiple
files and we would like them all to be the same. This can slow down the
merger an order of magnitude !!! *)letmerge_inlines=reffalseletmergeInlinesRepeat()=!merge_inlines&&trueletmergeInlinesWithAlphaConvert()=!merge_inlines&&true(* when true, merge duplicate definitions of externally-visible functions;
this uses a mechanism which is faster than the one for inline functions,
but only probabilistically accurate *)letmergeGlobals=true(* C99: inline functions are internal unless specified to be external
GNU89: inline functions are external unless specified to be static or extern
GNU89 inline semantics is used also when gnu_inline attribute is present on all inline declarations *)letexternallyVisiblevi=matchvi.vstoragewith|Static->false|_->(match!Cil.cstd,!Cil.gnu89inline,hasAttribute"gnu_inline"(typeAttrsvi.vtype)with|Cil.C90,_,_|_,true,_|_,_,true->notvi.vinline||vi.vstorage<>Extern|_,_,_->notvi.vinline||vi.vstorage=Extern)(* Return true if 's' starts with the prefix 'p' *)letprefixps=letlp=String.lengthpinletls=String.lengthsinlp<=ls&&String.subs0lp=p(* A name is identified by the index of the file in which it occurs (starting
at 0 with the first file) and by the actual name. We'll keep name spaces
separate *)(* We define a data structure for the equivalence classes *)type'anode={nname:string;(* The actual name *)nfidx:int;(* The file index *)ndata:'a;(* Data associated with the node *)mutablenloc:(location*int)option;(* location where defined and index within the file of the definition.
If None then it means that this node actually DOES NOT appear in the
given file. In rare occasions we need to talk in a given file about
types that are not defined in that file. This happens with undefined
structures but also due to cross-contamination of types in a few of
the cases of combineType (see the definition of combineTypes). We
try never to choose as representatives nodes without a definition.
We also choose as representative the one that appears earliest *)mutablenrep:'anode;(* A pointer to another node in its class (one
closer to the representative). The nrep node
is always in an earlier file, except for the
case where a name is undefined in one file
and defined in a later file. If this pointer
points to the node itself then this is the
representative. *)mutablenmergedSyns:bool;(* Whether we have merged the synonyms for
the node of this name *)}letd_nloc()(lo:(location*int)option):P.doc=matchlowith|None->P.text"None"|Some(l,idx)->P.dprintf"Some(%d at %a)"idxd_locl(* Make a node with a self loop. This is quite tricky. *)letmkSelfNode(eq:(int*string,'anode)H.t)(* The equivalence table *)(syn:(string,'anode)H.t)(* The synonyms table *)(fidx:int)(name:string)(data:'a)(l:(location*int)option)=letrecres={nname=name;nfidx=fidx;ndata=data;nloc=l;nrep=res;nmergedSyns=false;}inH.addeq(fidx,name)res;(* Add it to the proper table *)ifmergeSynonyms&¬(prefix"__anon"name)thenH.addsynnameres;resletdebugFind=false(* Find the representative with or without path compression *)letrecfind(pathcomp:bool)(nd:'anode)=ifdebugFindthenignore(E.log" find %s(%d)\n"nd.nnamend.nfidx);ifnd.nrep==ndthen(ifdebugFindthenignore(E.log" = %s(%d)\n"nd.nnamend.nfidx);nd)elseletres=findpathcompnd.nrepinifusePathCompression&&pathcomp&&nd.nrep!=resthennd.nrep<-res;(* Compress the paths *)res(* Union two nodes and return the new representative. We prefer as the
representative a node defined earlier. We try not to use as
representatives nodes that are not defined in their files. We return a
function for undoing the union. Make sure that between the union and the
undo you do not do path compression *)letunion(nd1:'anode)(nd2:'anode):'anode*(unit->unit)=(* Move to the representatives *)letnd1=findtruend1inletnd2=findtruend2inifnd1==nd2then((* It can happen that we are trying to union two nodes that are already
equivalent. This is because between the time we check that two nodes
are not already equivalent and the time we invoke the union operation
we check type isomorphism which might change the equivalence classes *)(*
ignore (warn "unioning already equivalent nodes for %s(%d)"
nd1.nname nd1.nfidx);
*)nd1,funx->x)elseletrep,norep=(* Choose the representative *)ifnd1.nloc!=None=(nd2.nloc!=None)then(if(* They have the same defined status. Choose the earliest *)nd1.nfidx<nd2.nfidxthen(nd1,nd2)elseifnd1.nfidx>nd2.nfidxthen(nd2,nd1)else(* In the same file. Choose the one with the earliest index *)match(nd1.nloc,nd2.nloc)with|Some(_,didx1),Some(_,didx2)->ifdidx1<didx2then(nd1,nd2)elseifdidx1>didx2then(nd2,nd1)else(ignore(warn"Merging two elements (%s and %s) in the same file (%d) \
with the same idx (%d) within the file"nd1.nnamend2.nnamend1.nfidxdidx1);(nd1,nd2))|_,_->(* both none. Does not matter which one we choose. Should
not happen though. *)(* sm: it does happen quite a bit when, e.g. merging STLport with
some client source; I'm disabling the warning since it supposedly
is harmless anyway, so is useless noise *)(* sm: re-enabling on claim it now will probably not happen *)ignore(warn"Merging two undefined elements in the same file: %s and %s"nd1.nnamend2.nname);(nd1,nd2))elseif(* One is defined, the other is not. Choose the defined one *)nd1.nloc!=Nonethen(nd1,nd2)else(nd2,nd1)inletoldrep=norep.nrepinnorep.nrep<-rep;(rep,fun()->norep.nrep<-oldrep)(*
let union (nd1: 'a node) (nd2: 'a node) : 'a node * (unit -> unit) =
if nd1 == nd2 && nd1.nname = "!!!intEnumInfo!!!" then begin
ignore (warn "unioning two identical nodes for %s(%d)"
nd1.nname nd1.nfidx);
nd1, fun x -> x
end else
union nd1 nd2
*)(* Find the representative for a node and compress the paths in the process *)letfindReplacement(pathcomp:bool)(eq:(int*string,'anode)H.t)(fidx:int)(name:string):('a*int)option=ifdebugFindthenignore(E.log"findReplacement for %s(%d)\n"namefidx);tryletnd=H.findeq(fidx,name)inifnd.nrep==ndthen(ifdebugFindthenignore(E.log" is a representative\n");None(* No replacement if this is the representative of its class *))elseletrep=findpathcompndinifrep!=rep.nrepthenE.s(bug"find does not return the representative\n");ifdebugFindthenignore(E.log" RES = %s(%d)\n"rep.nnamerep.nfidx);Some(rep.ndata,rep.nfidx)withNot_found->ifdebugFindthenignore(E.log" not found in the map\n");None(* Make a node if one does not already exist. Otherwise return the
representative *)letgetNode(eq:(int*string,'anode)H.t)(syn:(string,'anode)H.t)(fidx:int)(name:string)(data:'a)(l:(location*int)option)=letdebugGetNode=falseinifdebugGetNodethenignore(E.log"getNode(%s(%d), %a)\n"namefidxd_nlocl);tryletres=H.findeq(fidx,name)in(match(res.nloc,l)with(* Maybe we have a better location now *)|None,Some_->res.nloc<-l|Some(old_l,old_idx),Some(l,idx)->ifold_idx!=idxthenignore(warn"Duplicate definition of node %s(%d) at indices %d(%a) and \
%d(%a)"namefidxold_idxd_locold_lidxd_locl)else()|_,_->());ifdebugGetNodethenignore(E.log" node already found\n");findfalseres(* No path compression *)withNot_found->letres=mkSelfNodeeqsynfidxnamedatalinifdebugGetNodethenignore(E.log" made a new one\n");res(* Dump a graph *)letdumpGraph(what:string)(eq:(int*string,'anode)H.t):unit=ignore(E.log"Equivalence graph for %s is:\n"what);H.iter(fun(fidx,name)nd->ignore(E.log" %s(%d) %s-> "namefidx(ifnd.nloc=Nonethen"(undef)"else""));ifnd.nrep==ndthenignore(E.log"*\n")elseignore(E.log" %s(%d)\n"nd.nrep.nnamend.nrep.nfidx))eq(* For each name space we define a set of equivalence classes *)letvEq:(int*string,varinfonode)H.t=H.create111(* Vars *)letsEq:(int*string,compinfonode)H.t=H.create111(* Struct + union *)leteEq:(int*string,enuminfonode)H.t=H.create111(* Enums *)lettEq:(int*string,typeinfonode)H.t=H.create111(* Type names*)letiEq:(int*string,varinfonode)H.t=H.create111(* Inlines *)(* Sometimes we want to merge synonyms. We keep some tables indexed by names.
Each name is mapped to multiple entries *)letvSyn:(string,varinfonode)H.t=H.create111(* Not actually used *)letiSyn:(string,varinfonode)H.t=H.create111(* Inlines *)letsSyn:(string,compinfonode)H.t=H.create111leteSyn:(string,enuminfonode)H.t=H.create111lettSyn:(string,typeinfonode)H.t=H.create111(** A global environment for variables. Put in here only the non-static
variables, indexed by their name. *)letvEnv:(string,varinfonode)H.t=H.create111(* A set of inline functions indexed by their printout ! *)letinlineBodies:(P.doc,varinfonode)H.t=H.create111(** A number of alpha conversion tables. We ought to keep one table for each
name space. Unfortunately, because of the way the C lexer works, type
names must be different from variable names!! We one alpha table both for
variables and types. *)letvtAlpha:(string,locationA.alphaTableDataref)H.t=H.create57(* Variables and types *)letsAlpha:(string,locationA.alphaTableDataref)H.t=H.create57(* Structures and unions have the same name space *)leteAlpha:(string,locationA.alphaTableDataref)H.t=H.create57(* Enumerations *)(** Keep track, for all global function definitions, of the names of the formal
arguments. They might change during merging of function types if the
prototype occurs after the function definition and uses different names.
We'll restore the names at the end *)letformalNames:(int*string,stringlist)H.t=H.create111(* Accumulate here the globals in the merged file *)lettheFileTypes=ref[]lettheFile=ref[](* add 'g' to the merged file *)letmergePushGlobal(g:global):unit=pushGlobalg~types:theFileTypes~variables:theFileletmergePushGlobalsgl=List.itermergePushGlobalgl(* The index of the current file being scanned *)letcurrentFidx=ref0letcurrentDeclIdx=ref0(* The index of the definition in a file. This is
maintained both in pass 1 and in pass 2. Make
sure you count the same things in both passes. *)(* Keep here the file names *)letfileNames:(int,string)H.t=H.create113(* Remember the composite types that we have already declared *)letemittedCompDecls:(string,bool)H.t=H.create113(* Remember the variables also *)letemittedVarDecls:(string,bool)H.t=H.create113(* also keep track of externally-visible function definitions;
name maps to declaration, location, and semantic checksum *)letemittedFunDefn:(string,fundec*location*int)H.t=H.create113(* and same for variable definitions; name maps to GVar fields *)letemittedVarDefn:(string,varinfo*initoption*location)H.t=H.create113(** A mapping from the new names to the original names. Used in PASS2 when we
rename variables. *)letoriginalVarNames:(string,string)H.t=H.create113(* Initialize the module *)letinit()=H.clearsAlpha;H.cleareAlpha;H.clearvtAlpha;H.clearvEnv;H.clearvEq;H.clearsEq;H.cleareEq;H.cleartEq;H.cleariEq;H.clearvSyn;H.clearsSyn;H.cleareSyn;H.cleartSyn;H.cleariSyn;theFile:=[];theFileTypes:=[];H.clearformalNames;H.clearinlineBodies;currentFidx:=0;currentDeclIdx:=0;H.clearfileNames;H.clearemittedVarDecls;H.clearemittedCompDecls;H.clearemittedFunDefn;H.clearemittedVarDefn;H.clearoriginalVarNames(* Some enumerations have to be turned into an integer. We implement this by
introducing a special enumeration type which we'll recognize later to be
an integer *)letintEnumInfo={ename="!!!intEnumInfo!!!";(* This is otherwise invalid *)eitems=[];eattr=[];ereferenced=false;ekind=IInt;}(* And add it to the equivalence graph *)letintEnumInfoNode=getNodeeEqeSyn0intEnumInfo.enameintEnumInfo(Some(locUnknown,0))(* Combine the types. Raises the Failure exception with an error message.
isdef says whether the new type is for a definition *)typecombineWhat=|CombineFundef(* The new definition is for a function definition. The old
is for a prototype *)|CombineFunarg(* Comparing a function argument type with an old prototype
arg *)|CombineFunret(* Comparing the return of a function with that from an old
prototype *)|CombineOther(** Construct the composite type of [oldt] and [t] if they are compatible.
Raise [Failure] if they are incompatible. *)letreccombineTypes(what:combineWhat)(oldfidx:int)(oldt:typ)(fidx:int)(t:typ):typ=letoldq,olda=partitionQualifierAttributes(typeAttrsOuteroldt)inletq,a=partitionQualifierAttributes(typeAttrsOutert)inifoldq<>qthenraise(Failure(P.sprint~width:80(P.dprintf"(different type qualifiers %a and %a)"d_attrlistoldqd_attrlistq)))elseifq<>[]thentypeAddAttributesq(combineTypeswhatoldfidx(setTypeAttrsoldtolda)fidx(setTypeAttrsta))elsematch(oldt,t)with|TVoidolda,TVoida->TVoid(addAttributesoldaa)|TInt(oldik,olda),TInt(ik,a)->letcombineIKoldkk=ifoldk==kthenoldkelseif(* GCC allows a function definition to have a more precise integer
type than a prototype that says "int" *)oldk=IInt&&bitsSizeOft<=32&&(what=CombineFunarg||what=CombineFunret)thenkelseletmsg=P.sprint~width:80(P.dprintf"(different integer types %a and %a)"d_typeoldtd_typet)inraise(Failuremsg)inTInt(combineIKoldikik,addAttributesoldaa)|TFloat(oldfk,olda),TFloat(fk,a)->letcombineFKoldkk=ifoldk==kthenoldkelseif(* GCC allows a function definition to have a more precise integer
type than a prototype that says "double" *)oldk=FDouble&&k=FFloat&&(what=CombineFunarg||what=CombineFunret)thenkelseraise(Failure"(different floating point types)")inTFloat(combineFKoldfkfk,addAttributesoldaa)|TEnum(oldei,olda),TEnum(ei,a)->(* Matching enumerations always succeeds. But sometimes it maps both
enumerations to integers *)matchEnumInfooldfidxoldeifidxei;TEnum(oldei,addAttributesoldaa)(* Strange one. But seems to be handled by GCC *)|TEnum(oldei,olda),TInt(IInt,a)->TEnum(oldei,addAttributesoldaa)(* Strange one. But seems to be handled by GCC. Warning. Here we are
leaking types from new to old *)|TInt(IInt,olda),TEnum(ei,a)->TEnum(ei,addAttributesoldaa)|TComp(oldci,olda),TComp(ci,a)->matchCompInfooldfidxoldcifidxci;(* If we get here we were successful *)TComp(oldci,addAttributesoldaa)|TArray(oldbt,oldsz,olda),TArray(bt,sz,a)->letcombbt=combineTypesCombineOtheroldfidxoldbtfidxbtinletcombinesz=match(oldsz,sz)with|None,Some_->sz|Some_,None->oldsz|None,None->oldsz|Someoldsz',Somesz'->letsamesz=match(constFoldtrueoldsz',constFoldtruesz')with|Const(CInt(oldi,_,_)),Const(CInt(i,_,_))->Cilint.compare_cilintoldii=0|_,_->falseinifsameszthenoldszelseraise(Failure"(different array sizes)")inTArray(combbt,combinesz,addAttributesoldaa)|TPtr(oldbt,olda),TPtr(bt,a)->TPtr(combineTypesCombineOtheroldfidxoldbtfidxbt,addAttributesoldaa)(* WARNING: In this case we are leaking types from new to old !! *)|TFun(_,_,_,[Attr("missingproto",_)]),TFun_->t|TFun_,TFun(_,_,_,[Attr("missingproto",_)])->oldt|TFun(oldrt,oldargs,oldva,olda),TFun(rt,args,va,a)->letnewrt=combineTypes(ifwhat=CombineFundefthenCombineFunretelseCombineOther)oldfidxoldrtfidxrtinifoldva!=vathenraise(Failure"(different vararg specifiers)");(* If one does not have arguments, believe the one with the
arguments *)letnewargs=ifoldargs=Nonethenargselseifargs=Nonethenoldargselseletoldargslist=argsToListoldargsinletargslist=argsToListargsinifList.lengtholdargslist<>List.lengthargslistthenraise(Failure"(different number of arguments)")else(* Go over the arguments and update the old ones with the
adjusted types *)Some(List.map2(fun(on,ot,oa)(an,at,aa)->letn=ifan<>""thenanelseoninlett=combineTypes(ifwhat=CombineFundefthenCombineFunargelseCombineOther)oldfidx(removeOuterQualifierAttributesot)fidx(removeOuterQualifierAttributesat)inleta=addAttributesoaaain(n,t,a))oldargslistargslist)inTFun(newrt,newargs,oldva,addAttributesoldaa)|TBuiltin_va_listolda,TBuiltin_va_lista->TBuiltin_va_list(addAttributesoldaa)|TNamed(oldt,olda),TNamed(t,a)->matchTypeInfooldfidxoldtfidxt;(* If we get here we were able to match *)TNamed(oldt,addAttributesoldaa)(* Unroll first the new type *)|_,TNamed(t,a)->letres=combineTypeswhatoldfidxoldtfidxt.ttypeintypeAddAttributesares(* And unroll the old type as well if necessary *)|TNamed(oldt,a),_->letres=combineTypeswhatoldfidxoldt.ttypefidxtintypeAddAttributesares|_->(* raise (Failure "(different type constructors)") *)letmsg:string=P.sprint~width:1000(P.dprintf"(different type constructors: %a vs. %a)"d_typeoldtd_typet)inraise(Failuremsg)(* Match two compinfos and throw a Failure if they do not match *)andmatchCompInfo(oldfidx:int)(oldci:compinfo)(fidx:int)(ci:compinfo):unit=ifoldci.cstruct<>ci.cstructthenraise(Failure"(different struct/union types)");(* See if we have a mapping already *)(* Make the nodes if not already made. Actually return the
representatives *)letoldcinode=getNodesEqsSynoldfidxoldci.cnameoldciNoneinletcinode=getNodesEqsSynfidxci.cnameciNoneinifoldcinode==cinodethen(* We already know they are the same *)()else(* Replace with the representative data *)letoldci=oldcinode.ndatainletoldfidx=oldcinode.nfidxinletci=cinode.ndatainletfidx=cinode.nfidxinletold_len=List.lengtholdci.cfieldsinletlen=List.lengthci.cfieldsin(* It is easy to catch here the case when the new structure is undefined
and the old one was defined. We just reuse the old *)(* More complicated is the case when the old one is not defined but the
new one is. We still reuse the old one and we'll take care of defining
it later with the new fields.
GN: 7/10/04, I could not find when is "later", so I added it below *)iflen<>0&&old_len<>0&&old_len<>lenthen(letcurLoc=!currentLocin(* d_global blows this away.. *)trace"merge"(P.dprintf"different # of fields\n%d: %a\n%d: %a\n"old_lend_global(GCompTag(oldci,locUnknown))lend_global(GCompTag(ci,locUnknown)));currentLoc:=curLoc;letmsg=Printf.sprintf"(different number of fields in %s and %s: %d != %d.)"oldci.cnameci.cnameold_lenleninraise(Failuremsg));(* We check that they are defined in the same way. While doing this there
might be recursion and we have to watch for going into an infinite
loop. So we add the assumption that they are equal *)letnewrep,undo=unionoldcinodecinodein(* We check the fields but watch for Failure. We only do the check when
the lengths are the same. Due to the code above this the other
possibility is that one of the length is 0, in which case we reuse the
old compinfo. *)(* But what if the old one is the empty one ? *)ifold_len=lenthen(tryList.iter2(funoldff->ifoldf.fbitfield<>f.fbitfieldthenraise(Failure"(different bitfield info)");ifoldf.fattr<>f.fattrthenraise(Failure"(different field attributes)");(* Make sure the types are compatible *)letnewtype=combineTypesCombineOtheroldfidxoldf.ftypefidxf.ftypein(* Change the type in the representative *)oldf.ftype<-newtype)oldci.cfieldsci.cfieldswithFailurereason->(* Our assumption was wrong. Forget the isomorphism *)undo();letmsg=P.sprint~width:80(P.dprintf"\n\tFailed assumption that %s and %s are isomorphic %s@!%a@!%a"(compFullNameoldci)(compFullNameci)reasondn_global(GCompTag(oldci,locUnknown))dn_global(GCompTag(ci,locUnknown)))inraise(Failuremsg))elseif(* We will reuse the old one. One of them is empty. If the old one is
empty, copy over the fields from the new one. Won't this result in
all sorts of undefined types??? *)old_len=0thenoldci.cfields<-ci.cfields;(* We get here when we succeeded checking that they are equal, or one of
them was empty *)newrep.ndata.cattr<-addAttributesoldci.cattrci.cattr;()(* Match two enuminfos and throw a Failure if they do not match *)andmatchEnumInfo(oldfidx:int)(oldei:enuminfo)(fidx:int)(ei:enuminfo):unit=(* Find the node for this enum, no path compression. *)letoldeinode=getNodeeEqeSynoldfidxoldei.enameoldeiNoneinleteinode=getNodeeEqeSynfidxei.enameeiNoneinifoldeinode==einodethen(* We already know they are the same *)()else(* Replace with the representative data *)letoldei=oldeinode.ndatainletei=einode.ndatain(* Try to match them. But if you cannot just make them both integers *)try(* We do not have a mapping. They better be defined in the same way *)ifList.lengtholdei.eitems<>List.lengthei.eitemsthenraise(Failure"(different number of enumeration elements)");(* We check that they are defined in the same way. This is a fairly
conservative check. *)List.iter2(fun(old_iname,old_attrs,old_iv,_)(iname,attrs,iv,_)->ifold_iname<>inamethenraise(Failure"(different names for enumeration items)");ifold_attrs<>attrsthenraise(Failure"(different enumerator attributes)");letsamev=match(constFoldtrueold_iv,constFoldtrueiv)with|Const(CInt(oldi,_,_)),Const(CInt(i,_,_))->Cilint.compare_cilintoldii=0|_->falseinifnotsamevthenraise(Failure"(different values for enumeration items)"))oldei.eitemsei.eitems;(* Set the representative *)letnewrep,_=unionoldeinodeeinodein(* We get here if the enumerations match *)newrep.ndata.eattr<-addAttributesoldei.eattrei.eattr;()withFailuremsg->(* Get here if you cannot merge two enumeration nodes *)(ifoldeinode!=intEnumInfoNodethenlet_=unionoldeinodeintEnumInfoNodein());ifeinode!=intEnumInfoNodethenlet_=unioneinodeintEnumInfoNodein()(* Match two typeinfos and throw a Failure if they do not match *)andmatchTypeInfo(oldfidx:int)(oldti:typeinfo)(fidx:int)(ti:typeinfo):unit=ifoldti.tname=""||ti.tname=""thenE.s(bug"matchTypeInfo for anonymous type\n");(* Find the node for this enum, no path compression. *)letoldtnode=getNodetEqtSynoldfidxoldti.tnameoldtiNoneinlettnode=getNodetEqtSynfidxti.tnametiNoneinifoldtnode==tnodethen(* We already know they are the same *)()else(* Replace with the representative data *)letoldti=oldtnode.ndatainletoldfidx=oldtnode.nfidxinletti=tnode.ndatainletfidx=tnode.nfidxin(* Check that they are the same *)(tryignore(combineTypesCombineOtheroldfidxoldti.ttypefidxti.ttype)withFailurereason->letmsg=P.sprint~width:80(P.dprintf"\n\tFailed assumption that %s and %s are isomorphic %s"oldti.tnameti.tnamereason)inraise(Failuremsg));let_=unionoldtnodetnodein()(* Scan all files and do two things *)(* 1. Initialize the alpha renaming tables with the names of the globals so
that when we come in the second pass to generate new names, we do not run
into conflicts. *)(* 2. For all declarations of globals unify their types. In the process
construct a set of equivalence classes on type names, structure and
enumeration tags *)(* 3. We clean the referenced flags *)letoneFilePass1(f:file):unit=H.addfileNames!currentFidxf.fileName;ifdebugMerge||!E.verboseFlagthenignore(E.log"Pre-merging (%d) %s\n"!currentFidxf.fileName);currentDeclIdx:=0;iff.globinitcalled||f.globinit<>NonethenE.s(E.warn"Merging file %s has global initializer"f.fileName);(* We scan each file and we look at all global varinfo. We see if globals
with the same name have been encountered before and we merge those types
*)letmatchVarinfo(vi:varinfo)(l:location*int)=ignore(Alpha.registerAlphaName~alphaTable:vtAlpha~undolist:None~lookupname:vi.vname~data:!currentLoc);(* Make a node for it and put it in vEq *)letvinode=mkSelfNodevEqvSyn!currentFidxvi.vnamevi(Somel)intryletoldvinode=findtrue(H.findvEnvvi.vname)inletoldloc,_=matcholdvinode.nlocwith|None->E.s(bug"old variable is undefined")|Somel->linletoldvi=oldvinode.ndatain(* There is an old definition. We must combine the types. Do this first
because it might fail *)letnewtype=trycombineTypesCombineOtheroldvinode.nfidxoldvi.vtype!currentFidxvi.vtypewithFailurereason->(* Go ahead *)letf=if!ignore_merge_conflictsthenwarnelseerrorinignore(f"Incompatible declaration for %s (from %s(%d)).@! Previous was \
at %a (from %s (%d)) %s "vi.vname(H.findfileNames!currentFidx)!currentFidxd_locoldloc(H.findfileNamesoldvinode.nfidx)oldvinode.nfidxreason);raiseNot_foundinletnewrep,_=unionoldvinodevinodein(* We do not want to turn non-"const" globals into "const" one. That
can happen if one file declares the variable a non-const while
others declare it as "const". *)ifhasAttribute"const"(typeAttrsvi.vtype)!=hasAttribute"const"(typeAttrsoldvi.vtype)||hasAttribute"pconst"(typeAttrsvi.vtype)!=hasAttribute"pconst"(typeAttrsoldvi.vtype)thennewrep.ndata.vtype<-typeRemoveAttributes["const";"pconst"]newtypeelsenewrep.ndata.vtype<-newtype;(* clean up the storage. *)letnewstorage=ifvi.vstorage=oldvi.vstorage||vi.vstorage=Externthenoldvi.vstorageelseifoldvi.vstorage=Externthenvi.vstorage(* Sometimes we turn the NoStorage specifier into Static for inline
functions *)elseifoldvi.vstorage=Static&&vi.vstorage=NoStoragethenStaticelse(ignore(warn"Inconsistent storage specification for %s. Now is %a and \
previous was %a at %a"vi.vnamed_storagevi.vstoraged_storageoldvi.vstoraged_locoldloc);vi.vstorage)innewrep.ndata.vstorage<-newstorage;newrep.ndata.vattr<-addAttributesoldvi.vattrvi.vattr;()withNot_found->(* Not present in the previous files. Remember it for
later *)H.addvEnvvi.vnamevinodeinList.iter(function|GVarDecl(vi,l)|GVar(vi,_,l)->currentLoc:=l;incrcurrentDeclIdx;vi.vreferenced<-false;ifexternallyVisiblevithenmatchVarinfovi(l,!currentDeclIdx)|GFun(fdec,l)->currentLoc:=l;incrcurrentDeclIdx;(* Save the names of the formal arguments *)let_,args,_,_=splitFunctionTypeVIfdec.svarinH.addformalNames(!currentFidx,fdec.svar.vname)(Util.list_map(fun(fn,_,_)->fn)(argsToListargs));fdec.svar.vreferenced<-false;ifexternallyVisiblefdec.svarthen(* function with external linkage *)matchVarinfofdec.svar(l,!currentDeclIdx)elseiffdec.svar.vinline&&!merge_inlinesthen(* Just create the nodes for inline functions *)ignore(getNodeiEqiSyn!currentFidxfdec.svar.vnamefdec.svar(Some(l,!currentDeclIdx)))(* Make nodes for the defined type and structure tags *)|GType(t,l)->(incrcurrentDeclIdx;t.treferenced<-false;ift.tname<>""then(* The empty names are just for introducing
undefined comp tags *)ignore(getNodetEqtSyn!currentFidxt.tnamet(Some(l,!currentDeclIdx)))else(* Go inside and clean the referenced flag for the
declared tags *)matcht.ttypewith|TComp(ci,_)->ci.creferenced<-false;(* Create a node for it *)ignore(getNodesEqsSyn!currentFidxci.cnameciNone)|TEnum(ei,_)->ei.ereferenced<-false;ignore(getNodeeEqeSyn!currentFidxei.enameeiNone)|_->E.s(bug"Anonymous Gtype is not TComp"))|GCompTag(ci,l)->incrcurrentDeclIdx;ci.creferenced<-false;ignore(getNodesEqsSyn!currentFidxci.cnameci(Some(l,!currentDeclIdx)))|GEnumTag(ei,l)->incrcurrentDeclIdx;ei.ereferenced<-false;ignore(getNodeeEqeSyn!currentFidxei.enameei(Some(l,!currentDeclIdx)))|_->())f.globals(* Try to merge synonyms. Do not give an error if they fail to merge *)letdoMergeSynonyms(syn:(string,'anode)H.t)(eq:(int*string,'anode)H.t)(compare:int->'a->int->'a->unit):unit=(* A comparison function that
throws Failure if no match *)H.iter(funnnode->ifnotnode.nmergedSynsthen(* find all the nodes for the same name *)letall=H.find_allsynninlettryone(classes:'anodelist)(* A number of representatives
for this name *)(nd:'anode):'anodelist(* Returns an expanded set
of classes *)=nd.nmergedSyns<-true;(* Compare in turn with all the classes we have so far *)letreccompareWithClasses=function|[]->[nd](* No more classes. Add this as a new class *)|c::restc->(trycomparec.nfidxc.ndatand.nfidxnd.ndata;(* Success. Stop here the comparison *)c::restcwithFailure_->(* Failed. Try next class *)c::compareWithClassesrestc)incompareWithClassesclassesin(* Start with an empty set of classes for this name *)let_=List.fold_lefttryone[]allin())synletmatchInlines(oldfidx:int)(oldi:varinfo)(fidx:int)(i:varinfo)=letoldinode=getNodeiEqiSynoldfidxoldi.vnameoldiNoneinletinode=getNodeiEqiSynfidxi.vnameiNoneinifoldinode==inodethen()else(* Replace with the representative data *)letoldi=oldinode.ndatainletoldfidx=oldinode.nfidxinleti=inode.ndatainletfidx=inode.nfidxin(* There is an old definition. We must combine the types. Do this first
because it might fail *)oldi.vtype<-combineTypesCombineOtheroldfidxoldi.vtypefidxi.vtype;(* We get here if we have success *)(* Combine the attributes as well *)oldi.vattr<-addAttributesoldi.vattri.vattr;(* Do not union them yet because we do not know that they are the same.
We have checked only the types so far *)()(************************************************************
PASS 2
************************************************************)(** Keep track of the functions we have used already in the file. We need
this to avoid removing an inline function that has been used already.
This can only occur if the inline function is defined after it is used
already; a bad style anyway *)letvarUsedAlready:(string,unit)H.t=H.create111(** A visitor that renames uses of variables and types *)classrenameVisitorClass=object(self)inheritnopCilVisitor(* This is either a global variable which we took care of, or a local
variable. Must do its type and attributes. *)method!vvdec(vi:varinfo)=DoChildrenmethod!vglob(g:global):globallistvisitAction=matchgwith|GVar(v,init,loc)->letupdate_initglob=matchglobwith|GVar(u,uinit,loc)->GVar(u,u.vinit,loc)|_->globinletupdate_all_inits=List.mapupdate_initinlet()=match(v.vinit.init,init.init)with|None,None->()(* This case may happen when a definition is encountered, but
the variable was already seen through a declaration and thus
has no definition *)|None,Some_->v.vinit.init<-init.init(* The following case should never happen because it should never be emitted *)|Some_,None->assertfalse(* The following case is either never emitted (same
initializations, or different initializations but an error is
thrown) or emitted when first encountering a definition
(hence the initializations are supposed to be identical) *)|Some_,Some_->()inChangeDoChildrenPost([g],update_all_inits)|_->DoChildren(* This is a variable use. See if we must change it *)method!vvrbl(vi:varinfo):varinfovisitAction=ifnotvi.vglobthenDoChildrenelseifvi.vreferencedthen(H.addvarUsedAlreadyvi.vname();DoChildren)elsematchfindReplacementtruevEq!currentFidxvi.vnamewith|None->DoChildren|Some(vi',oldfidx)->ifdebugMergethenignore(E.log"Renaming use of var %s(%d) to %s(%d)\n"vi.vname!currentFidxvi'.vnameoldfidx);vi'.vreferenced<-true;H.addvarUsedAlreadyvi'.vname();ChangeTovi'(* The use of a type. Change only those types whose underlying info
is not a root. *)method!vtype(t:typ)=matchtwith|TComp(ci,a)whennotci.creferenced->(matchfindReplacementtruesEq!currentFidxci.cnamewith|None->DoChildren|Some(ci',oldfidx)->ifdebugMergethenignore(E.log"Renaming use of %s(%d) to %s(%d)\n"ci.cname!currentFidxci'.cnameoldfidx);ChangeTo(TComp(ci',visitCilAttributes(self:>cilVisitor)a)))|TEnum(ei,a)whennotei.ereferenced->(matchfindReplacementtrueeEq!currentFidxei.enamewith|None->DoChildren|Some(ei',_)->ifei'==intEnumInfothen(* This is actually our friend intEnumInfo *)ChangeTo(TInt(IInt,visitCilAttributes(self:>cilVisitor)a))elseChangeTo(TEnum(ei',visitCilAttributes(self:>cilVisitor)a)))|TNamed(ti,a)whennotti.treferenced->(matchfindReplacementtruetEq!currentFidxti.tnamewith|None->DoChildren|Some(ti',_)->ChangeTo(TNamed(ti',visitCilAttributes(self:>cilVisitor)a)))|_->DoChildren(* The Field offset might need to be changed to use new compinfo *)method!voffs=function|Field(f,o)->(if(* See if the compinfo was changed *)f.fcomp.creferencedthenDoChildrenelsematchfindReplacementtruesEq!currentFidxf.fcomp.cnamewith|None->DoChildren(* We did not replace it *)|Some(ci',oldfidx)->(* First, find out the index of the original field *)letrecindexOf(i:int)=function|[]->E.s(bug"Cannot find field %s in %s(%d)\n"f.fname(compFullNamef.fcomp)!currentFidx)|f'::restwhenf'==f->i|_::rest->indexOf(i+1)restinletindex=indexOf0f.fcomp.cfieldsinifList.lengthci'.cfields<=indexthenE.s(bug"Too few fields in replacement %s(%d) for %s(%d)\n"(compFullNameci')oldfidx(compFullNamef.fcomp)!currentFidx);letf'=List.nthci'.cfieldsindexinChangeDoChildrenPost(Field(f',o),funx->x))|_->DoChildrenmethod!vinitoffso=self#voffso(* treat initializer offsets same as lvalue offsets *)endletrenameVisitor=newrenameVisitorClass(** A visitor that renames uses of inline functions that were discovered in
pass 2 to be used before they are defined. This is like the renameVisitor
except it only looks at the variables (thus it is a bit more efficient)
and it also renames forward declarations of the inlines to be removed. *)classrenameInlineVisitorClass=object(self)inheritnopCilVisitor(* This is a variable use. See if we must change it *)method!vvrbl(vi:varinfo):varinfovisitAction=ifnotvi.vglobthenDoChildrenelseifvi.vreferencedthen(* Already renamed *)DoChildrenelsematchfindReplacementtruevEq!currentFidxvi.vnamewith|None->DoChildren|Some(vi',oldfidx)->ifdebugMergethenignore(E.log"Renaming var %s(%d) to %s(%d)\n"vi.vname!currentFidxvi'.vnameoldfidx);vi'.vreferenced<-true;ChangeTovi'(* And rename some declarations of inlines to remove. We cannot drop this
declaration (see small1/combineinline6) *)method!vglob=function|GVarDecl(vi,l)whenvi.vinline->((* Get the original name *)letorigname=tryH.findoriginalVarNamesvi.vnamewithNot_found->vi.vnamein(* Now see if this must be replaced *)matchfindReplacementtruevEq!currentFidxorignamewith|None->DoChildren|Some(vi',_)->ChangeTo[GVarDecl(vi',l)])|_->DoChildrenendletrenameInlinesVisitor=newrenameInlineVisitorClass(* sm: First attempt at a semantic checksum for function bodies.
Ideally, two function's checksums would be equal only when their
bodies were provably equivalent; but I'm using a much simpler and
less accurate heuristic here. It should be good enough for the
purpose I have in mind, which is doing duplicate removal of
multiply-instantiated template functions. *)letfunctionChecksum(dec:fundec):int=(* checksum the structure of the statements (only) *)letrecstmtListSum(lst:stmtlist):int=List.fold_left(funaccs->acc+stmtSums)0lstandstmtSum(s:stmt):int=(* strategy is to just throw a lot of prime numbers into the
computation in hopes of avoiding accidental collision.. *)matchs.skindwith|Instrl->13+(67*List.lengthl)|Return_->17|Goto_->19|ComputedGoto_->131|Break_->23|Continue_->29|If(_,b1,b2,_,_)->31+(37*stmtListSumb1.bstmts)+(41*stmtListSumb2.bstmts)|Switch(_,b,_,_,_)->43+(47*stmtListSumb.bstmts)(* don't look at stmt list b/c is not part of tree *)|Loop(b,_,_,_,_)->49+(53*stmtListSumb.bstmts)|Blockb->59+(61*stmtListSumb.bstmts)in(* disabled 2nd and 3rd measure because they appear to get different
values, for the same code, depending on whether the code was just
parsed into CIL or had previously been parsed into CIL, printed
out, then re-parsed into CIL *)leta,b,c,d,e=(List.lengthdec.sformals,(* # formals *)0(*(List.length dec.slocals)*),(* # locals *)0(*dec.smaxid*),(* estimate of internal statement count *)List.lengthdec.sbody.bstmts,(* number of statements at outer level *)stmtListSumdec.sbody.bstmts)in(* checksum of statement structure *)(*(trace "sm" (P.dprintf "sum: %s is %d %d %d %d %d\n"*)(* dec.svar.vname a b c d e));*)(2*a)+(3*b)+(5*c)+(7*d)+(11*e)(* sm: equality for initializers, etc.; this is like '=', except
when we reach shared pieces (like references into the type
structure), we use '==', to prevent circularity *)(* update: that's no good; I'm using this to find things which
are equal but from different CIL trees, so nothing will ever
be '=='.. as a hack I'll just change those places to 'true',
so these functions are not now checking proper equality..
places where equality is not complete are marked "INC" *)letrecequalInits(x:init)(y:init):bool=match(x,y)with|SingleInitxe,SingleInitye->equalExpsxeye|CompoundInit(xt,xoil),CompoundInit(yt,yoil)->(*(xt == yt) &&*)(* INC *)(* types need to be identically equal *)letrecequalListsxoilyoil:bool=match(xoil,yoil)with|(xo,xi)::xrest,(yo,yi)::yrest->equalOffsetsxoyo&&equalInitsxiyi&&equalListsxrestyrest|[],[]->true|_,_->falseinequalListsxoilyoil|_,_->falseandequalOffsets(x:offset)(y:offset):bool=match(x,y)with|NoOffset,NoOffset->true|Field(xfi,xo),Field(yfi,yo)->xfi.fname=yfi.fname&&(* INC: same fieldinfo name.. *)equalOffsetsxoyo|Index(xe,xo),Index(ye,yo)->equalExpsxeye&&equalOffsetsxoyo|_,_->falseandequalExps(x:exp)(y:exp):bool=match(x,y)with|Constxc,Constyc->(xc=yc||(* safe to use '=' on literals *)(* CIL changes (unsigned)0 into 0U during printing.. *)match(xc,yc)with|CInt(a,_,_),CInt(b,_,_)->Cilint.is_zero_cilinta&&Cilint.is_zero_cilintb(* ok if they're both 0 *)|_,_->false)|Lvalxl,Lvalyl->equalLvalsxlyl|SizeOfxt,SizeOfyt->true(*INC: xt == yt*)(* identical types *)|SizeOfExe,SizeOfEye->equalExpsxeye|AlignOfxt,AlignOfyt->true(*INC: xt == yt*)|AlignOfExe,AlignOfEye->equalExpsxeye|UnOp(xop,xe,xt),UnOp(yop,ye,yt)->xop=yop&&equalExpsxeye&&true(*INC: xt == yt*)|BinOp(xop,xe1,xe2,xt),BinOp(yop,ye1,ye2,yt)->xop=yop&&equalExpsxe1ye1&&equalExpsxe2ye2&&true(*INC: xt == yt*)|CastE(xt,xe),CastE(yt,ye)->(*INC: xt == yt &&*)equalExpsxeye|AddrOfxl,AddrOfyl->equalLvalsxlyl|StartOfxl,StartOfyl->equalLvalsxlyl(* initializers that go through CIL multiple times sometimes lose casts they
had the first time; so allow a different of a cast *)|CastE(xt,xe),ye->equalExpsxeye|xe,CastE(yt,ye)->equalExpsxeye|_,_->falseandequalLvals(x:lval)(y:lval):bool=match(x,y)with|(Varxv,xo),(Varyv,yo)->(* I tried, I really did.. the problem is I see these names
before merging collapses them, so __T123 != __T456,
so whatever *)(*(xv.vname = vy.vname) && (* INC: same varinfo names.. *)*)equalOffsetsxoyo|(Memxe,xo),(Memye,yo)->equalExpsxeye&&equalOffsetsxoyo|_,_->falseletequalInitOpts(x:initoption)(y:initoption):bool=match(x,y)with|None,None->true|Somexi,Someyi->equalInitsxiyi|_,_->false(* The comparion of inline functions is based on pretty printing (!?) *)letprintInlineForComparisonfdec'g'=(* Temporarily turn off printing of lines *)letoldprintln=!lineDirectiveStyleinlineDirectiveStyle:=None;(* Temporarily set the name to all functions in the same way *)letnewname=fdec'.svar.vnameinfdec'.svar.vname<-"@@alphaname@@";(* If we must do alpha conversion then temporarily set the
names of the local variables and formals in a standard way *)letnameId=ref0inletoldNames:stringlistref=ref[]inletrenameOne(v:varinfo)=oldNames:=v.vname::!oldNames;incrnameId;v.vname<-"___alpha"^string_of_int!nameIdinletundoRenameOne(v:varinfo)=match!oldNameswith|n::rest->oldNames:=rest;v.vname<-n|_->E.s(bug"undoRenameOne")in(* Remember the original type *)letorigType=fdec'.svar.vtypeinifmergeInlinesWithAlphaConvert()then((* Rename the formals *)List.iterrenameOnefdec'.sformals;(* Reflect in the type *)setFormalsfdec'fdec'.sformals;(* Now do the locals *)List.iterrenameOnefdec'.slocals);(* Now print it *)letres=d_global()g'inlineDirectiveStyle:=oldprintln;fdec'.svar.vname<-newname;ifmergeInlinesWithAlphaConvert()then((* Do the locals in reverse order *)List.iterundoRenameOne(List.revfdec'.slocals);(* Do the formals in reverse order *)List.iterundoRenameOne(List.revfdec'.sformals);(* Restore the type *)fdec'.svar.vtype<-origType);res(* Now we go once more through the file and we rename the globals that we
keep. We also scan the entire body and we replace references to the
representative types or variables. We set the referenced flags once we
have replaced the names. *)letoneFilePass2(f:file)=ifdebugMerge||!E.verboseFlagthenignore(E.log"Final merging phase (%d): %s\n"!currentFidxf.fileName);currentDeclIdx:=0;(* Even though we don't need it anymore *)H.clearvarUsedAlready;H.clearoriginalVarNames;(* If we find inline functions that are used before being defined, and thus
before knowing that we can throw them away, then we mark this flag so
that we can make another pass over the file *)letrepeatPass2=reffalsein(* Keep a pointer to the contents of the file so far *)letsavedTheFile=!theFileinletprocessOneGlobal(g:global):unit=(* Process a varinfo. Reuse an old one, or rename it if necessary *)letprocessVarinfo~isadef(vi:varinfo)(vloc:location):varinfo=ifvi.vreferencedthenvi(* Already done *)elseifnot(externallyVisiblevi)then(* rename static and not-external inline functions no matter if merge_inlines is enabled or not,
renaming is undone using originalVarNames in case merging is successful *)((* Maybe it is static or inline and we are not merging inlines. Rename it then *)letnewName,_=A.newAlphaName~alphaTable:vtAlpha~undolist:None~lookupname:vi.vname~data:!currentLocin(* Remember the original name *)H.addoriginalVarNamesnewNamevi.vname;ifdebugMergethenignore(E.log"renaming %s at %a to %s\n"vi.vnamed_locvlocnewName);vi.vname<-newName;vi.vid<-newVID();vi.vreferenced<-true;vi)else(* Find the representative *)matchfindReplacementtruevEq!currentFidxvi.vnamewith|None->vi(* This is the representative *)|Some(vi',_)->(* Reuse some previous one *)vi'.vreferenced<-true;(* Mark it as done already *)vi'.vaddrof<-vi.vaddrof||vi'.vaddrof;ifisadefthenvi'.vdecl<-vi.vdecl;vi'intrymatchgwith|GVarDecl(vi,l)asg->currentLoc:=l;incrcurrentDeclIdx;letvi'=processVarinfo~isadef:falsevilinifvi!=vi'then(* Drop this declaration *)()elseifH.mememittedVarDeclsvi'.vnamethen(* No need to keep it *)()else(H.addemittedVarDeclsvi'.vnametrue;(* Remember that we emitted it *)mergePushGlobals(visitCilGlobalrenameVisitorg))|GVar(vi,init,l)->currentLoc:=l;incrcurrentDeclIdx;letvi'=processVarinfo~isadef:(init.init<>None)vilin(* We must keep this definition even if we reuse this varinfo, because maybe the previous one was a declaration *)H.addemittedVarDeclsvi.vnametrue;ifmergeGlobalsthenmatchH.find_optemittedVarDefnvi'.vnamewith|None->(* no previous definition *)H.addemittedVarDefnvi'.vname(vi',init.init,l);mergePushGlobals(visitCilGlobalrenameVisitor(GVar(vi',init,l)))|Some(prevVar,prevInitOpt,prevLoc)->ifequalInitOptsprevInitOptinit.init||init.init=Nonethentrace"mergeGlob"(P.dprintf"dropping global var %s at %a in favor of the one at %a\n"vi'.vnamed_locld_locprevLoc)(* do not emit *)elseifprevInitOpt=Nonethen(* We have an initializer, but the previous one didn't. We should really convert the previous global from GVar to GVarDecl, but that's not convenient to do here. *)mergePushGlobals(visitCilGlobalrenameVisitor(GVar(vi',init,l)))else(* Both GVars have initializers. *)E.s(error"global var %s at %a has different initializer than %a"vi'.vnamed_locld_locprevLoc)else(* Not merging globals, nothing to be done*)mergePushGlobals(visitCilGlobalrenameVisitor(GVar(vi',init,l)))|GFun(fdec,l)asg->currentLoc:=l;incrcurrentDeclIdx;(* We apply the renaming *)fdec.svar<-processVarinfo~isadef:truefdec.svarl;(* Get the original name. *)letorigname=tryH.findoriginalVarNamesfdec.svar.vnamewithNot_found->fdec.svar.vnamein(* Go in there and rename everything as needed *)letfdec'=matchvisitCilGlobalrenameVisitorgwith|[GFun(fdec',_)]->fdec'|_->E.s(unimp"renameVisitor for GFun returned something else")inletg'=GFun(fdec',l)in(* Now restore the parameter names *)let_,args,_,_=splitFunctionTypeVIfdec'.svarin(matchH.find_optformalNames(!currentFidx,origname)with|Someoldnames->letargl=argsToListargsinifList.lengtholdnames<>List.lengtharglthenE.s(unimp"After merging the function has more arguments");List.iter2(funoldna->ifoldn<>""thena.vname<-oldn)oldnamesfdec.sformals;(* Reflect them in the type *)setFormalsfdecfdec.sformals|None->ignore(warnOpt"Cannot find %s in formalNames"origname));(* See if we can remove this inline function *)iffdec'.svar.vinline&&!merge_inlinesthen(letprintout=printInlineForComparisonfdec'g'in(* Make a node for this inline function using the original name. *)letinode=getNodevEqvSyn!currentFidxorignamefdec'.svar(Some(l,!currentDeclIdx))inifdebugInlinesthen(ignore(E.log"getNode %s(%d) with loc=%a. declidx=%d\n"inode.nnameinode.nfidxd_nlocinode.nloc!currentDeclIdx);ignore(E.log"Looking for previous definition of inline %s(%d)\n"origname!currentFidx));tryletoldinode=H.findinlineBodiesprintoutinifdebugInlinesthenignore(E.log" Matches %s(%d)\n"oldinode.nnameoldinode.nfidx);(* There is some other inline function with the same printout.
We should reuse this, but watch for the case when the inline
was already used. *)ifH.memvarUsedAlreadyfdec'.svar.vnamethenifmergeInlinesRepeat()thenrepeatPass2:=trueelse(ignore(warn"Inline function %s because it is used before it is defined"fdec'.svar.vname);raiseNot_found);let_=unionoldinodeinodein(* Clean up the vreferenced bit in the new inline, so that we
can rename it. Reset the name to the original one so that
we can find the replacement name. *)fdec'.svar.vreferenced<-false;fdec'.svar.vname<-origname;()(* Drop this definition *)withNot_found->ifdebugInlinesthenignore(E.log" Not found\n");H.addinlineBodiesprintoutinode;mergePushGlobalg')elseifmergeGlobals&¬(fdec'.svar.vstorage=Static||fdec'.svar.vinline)then((* !merge_inlines is false here anyway *)(* either the function is not inline, or we're not attempting to merge inlines *)(* sm: this is a non-inline, non-static function. I want to consider dropping it if a same-named function has already been put into the merged file *)letsum=functionChecksumfdec'in(*(trace "mergeGlob" (P.dprintf "I see extern function %s, sum is %d\n" fdec'.svar.vname curSum));*)matchH.find_optemittedFunDefnfdec'.svar.vnamewith|None->(* there was no previous definition *)mergePushGlobalg';H.addemittedFunDefnfdec'.svar.vname(fdec',l,sum)|Some(prevFun,prevLoc,prevSum)->(* previous was found *)ifsum=prevSumthentrace"mergeGlob"(P.dprintf"dropping duplicate def'n of func %s at %a in favor of that at %a\n"fdec'.svar.vnamed_locld_locprevLoc)else(* the checksums differ, so print a warning but keep the older one to avoid a link error later. *)(* I think this is a reasonable approximation of what ld does. *)ignore(warn"def'n of func %s at %a (sum %d) conflicts with the one at %a (sum %d); keeping the one at %a."fdec'.svar.vnamed_loclsumd_locprevLocprevSumd_locprevLoc))else(* not attempting to merge global functions, or it was static or inline *)mergePushGlobalg'|GCompTag(ci,l)asg->(currentLoc:=l;incrcurrentDeclIdx;ifci.creferencedthen()elsematchfindReplacementtruesEq!currentFidxci.cnamewith|None->(* A new one, we must rename it and keep the definition *)(* Make sure this is root *)(tryletnd=H.findsEq(!currentFidx,ci.cname)inifnd.nrep!=ndthenE.s(bug"Setting creferenced for struct %s(%d) which is not \
root!\n"ci.cname!currentFidx)withNot_found->E.s(bug"Setting creferenced for struct %s(%d) which is not in \
the sEq!\n"ci.cname!currentFidx));letnewname,_=A.newAlphaName~alphaTable:sAlpha~undolist:None~lookupname:ci.cname~data:!currentLocinci.cname<-newname;ci.creferenced<-true;ci.ckey<-H.hash(compFullNameci);(* Now we should visit the fields as well *)H.addemittedCompDeclsci.cnametrue;(* Remember that we
emitted it *)mergePushGlobals(visitCilGlobalrenameVisitorg)|Some(oldci,oldfidx)->(* We are not the representative. Drop this declaration
because we'll not be using it. *)())|GEnumTag(ei,l)asg->(currentLoc:=l;incrcurrentDeclIdx;ifei.ereferencedthen()elsematchfindReplacementtrueeEq!currentFidxei.enamewith|None->(* We must rename it *)letnewname,_=A.newAlphaName~alphaTable:eAlpha~undolist:None~lookupname:ei.ename~data:!currentLocinei.ename<-newname;ei.ereferenced<-true;(* And we must rename the items to using the same name space
as the variables *)ei.eitems<-Util.list_map(fun(n,attrs,i,loc)->letnewname,_=A.newAlphaName~alphaTable:vtAlpha~undolist:None~lookupname:n~data:!currentLocin(newname,attrs,i,loc))ei.eitems;mergePushGlobals(visitCilGlobalrenameVisitorg)|Some(ei',_)->(* Drop this since we are reusing it from
before *)())|GCompTagDecl(ci,l)->currentLoc:=l;(* This is here just to introduce an undefined
structure. But maybe the structure was defined
already. *)(* Do not increment currentDeclIdx because it is not incremented in
pass 1*)ifH.mememittedCompDeclsci.cnamethen()(* It was already declared *)else(H.addemittedCompDeclsci.cnametrue;(* Keep it as a declaration *)mergePushGlobalg)|GEnumTagDecl(ei,l)->currentLoc:=l;(* Do not increment currentDeclIdx because it is not incremented in
pass 1*)(* Keep it as a declaration *)mergePushGlobalg|GType(ti,l)asg->(currentLoc:=l;incrcurrentDeclIdx;ifti.treferencedthen()elsematchfindReplacementtruetEq!currentFidxti.tnamewith|None->(* We must rename it and keep it *)letnewname,_=A.newAlphaName~alphaTable:vtAlpha~undolist:None~lookupname:ti.tname~data:!currentLocinti.tname<-newname;ti.treferenced<-true;mergePushGlobals(visitCilGlobalrenameVisitorg)|Some(ti',_)->(* Drop this since we are reusing it from
before *)())|g->mergePushGlobals(visitCilGlobalrenameVisitorg)withe->letglobStr:string=P.sprint~width:1000(P.dprintf"error when merging global %a: %s"d_globalg(Printexc.to_stringe))inignore(E.log"%s"globStr);(*"error when merging global: %s" (Printexc.to_string e);*)mergePushGlobal(GText(P.sprint~width:80(P.dprintf"/* error at %t:"d_thisloc)));mergePushGlobalg;mergePushGlobal(GText"*************** end of error*/");raiseein(* Now do the real PASS 2 *)List.iterprocessOneGlobalf.globals;(* See if we must re-visit the globals in this file because an inline that
is being removed was used before we saw the definition and we decided to
remove it *)ifmergeInlinesRepeat()&&!repeatPass2then(ifdebugMerge||!E.verboseFlagthenignore(E.log"Repeat final merging phase (%d): %s\n"!currentFidxf.fileName);(* We are going to rescan the globals we have added while processing this
file. *)lettheseGlobals:globallistref=ref[]in(* Scan a list of globals until we hit a given tail *)letrecscanUntil(tail:'alist)(l:'alist)=iftail==lthen()elsematchlwith|[]->E.s(bug"mergecil: scanUntil could not find the marker\n")|g::rest->theseGlobals:=g::!theseGlobals;scanUntiltailrestin(* Collect in theseGlobals all the globals from this file *)theseGlobals:=[];scanUntilsavedTheFile!theFile;(* Now reprocess them *)theFile:=savedTheFile;List.iter(fung->theFile:=visitCilGlobalrenameInlinesVisitorg@!theFile)!theseGlobals(* Now check if we have inlines that we could not remove
H.iter (fun name _ ->
if not (H.mem inlinesRemoved name) then
ignore (warn "Could not remove inline %s. I have no idea why!"
name))
inlinesToRemove *))letmerge(files:filelist)(newname:string):file=init();(* Make the first pass over the files *)currentFidx:=0;List.iter(funf->oneFilePass1f;incrcurrentFidx)files;(* Now maybe try to force synonyms to be equal *)ifmergeSynonymsthen(doMergeSynonymssSynsEqmatchCompInfo;doMergeSynonymseSyneEqmatchEnumInfo;doMergeSynonymstSyntEqmatchTypeInfo;if!merge_inlinesthen((* Copy all the nodes from the iEq to vEq as well. This is needed
because vEq will be used for variable renaming *)H.iter(funkn->H.addvEqkn)iEq;doMergeSynonymsiSyniEqmatchInlines));(* Now maybe dump the graph *)ifdebugMergethen(dumpGraph"type"tEq;dumpGraph"struct and union"sEq;dumpGraph"enum"eEq;dumpGraph"variable"vEq;if!merge_inlinesthendumpGraph"inline"iEq);(* Make the second pass over the files. This is when we start rewriting the
file *)currentFidx:=0;List.iter(funf->oneFilePass2f;incrcurrentFidx)files;(* Now reverse the result and return the resulting file *)letrecrevontoacc=function[]->acc|x::t->revonto(x::acc)tinletres={fileName=newname;globals=revonto(revonto[]!theFile)!theFileTypes;globinit=None;globinitcalled=false;}ininit();(* Make the GC happy *)(* We have made many renaming changes and sometimes we have just guessed a
name wrong. Make sure now that the local names are unique. *)uniqueVarNamesres;res