12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106(*
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.
*)(* A consistency checker for CIL *)openCilmoduleE=ErrormsgmoduleH=HashtblopenPretty(* A few parameters to customize the checking *)typecheckFlags=NoCheckGlobalIds(* Do not check that the global ids have the proper
hash value *)|IgnoreInstructionsof(instr->bool)(* Ignore the specified instructions *)letcheckGlobalIds=reftrueletignoreInstr=ref(funi->false)letvalid=reftrueletwarnfmt=valid:=false;Cil.warn("CIL invariant broken: "^^fmt)letwarnContextfmt=valid:=false;Cil.warnContextfmtletcheckAttributes(attrs:attributelist):unit=letreclooplastname=function[]->()|Attr(an,_)::resta->ifan<lastnamethenignore(warn"Attributes not sorted");loopanrestainloop""attrs(* Keep track of defined types *)lettypeDefs:(string,typ)H.t=H.create117(* TODO: unused *)(* Keep track of all variables names, enum tags and type names *)letvarNamesEnv:(string,unit)H.t=H.create117(* We also keep a map of variables indexed by id, to ensure that only one
varinfo has a given id *)letvarIdsEnv:(int,varinfo)H.t=H.create117(* And keep track of all varinfo's to check the uniqueness of the
identifiers *)letallVarIds:(int,varinfo)H.t=H.create117letfundecForVarIds:(int,unit)H.t=H.create117(* Also keep a list of environments. We place an empty string in the list to
mark the start of a local environment (i.e. a function) *)letvarNamesList:(string*int)listref=ref[]letdefineNames=ifs=""thenE.s(bug"Empty name\n");ifH.memvarNamesEnvsthenignore(warn"Multiple definitions for %s"s);H.addvarNamesEnvs()letdefineVariablevi=(* E.log "saw %s: %d\n" vi.vname vi.vid; *)defineNamevi.vname;varNamesList:=(vi.vname,vi.vid)::!varNamesList;(* Check the id *)ifH.memallVarIdsvi.vidthenignore(warn"Id %d is already defined (%s)"vi.vidvi.vname);H.addallVarIdsvi.vidvi;(* And register it in the current scope also *)H.addvarIdsEnvvi.vidvi(* Check that a varinfo has already been registered *)letcheckVariablevi=try(* Check in the current scope only *)letold=H.findvarIdsEnvvi.vidinifvi!=oldthenbeginifvi.vname=old.vnamethenignore(warnContext"varinfos for %s not shared"vi.vname)elseignore(warnContext"variables %s and %s share id %d"vi.vnameold.vnamevi.vid)endwithNot_found->ignore(warn"Unknown id (%d) for %s"vi.vidvi.vname)letstartEnv()=varNamesList:=("",-1)::!varNamesListletendEnv()=letrecloop=function[]->E.s(bug"Cannot find start of env")|("",_)::rest->varNamesList:=rest|(s,id)::rest->beginH.removevarNamesEnvs;H.removevarIdsEnvid;looprestendinloop!varNamesList(* The current function being checked *)letcurrentReturnType:typref=refvoidType(* A map of labels in the current function *)letlabels:(string,unit)H.t=H.create17(* A list of statements seen in the current function *)letstatements:stmtlistref=ref[](* A list of the targets of Gotos *)letgotoTargets:(string*stmt)listref=ref[](*** TYPES ***)(* Certain types can only occur in some contexts, so keep a list of context *)typectxType=CTStruct(* In a composite type *)|CTUnion|CTFArg(* In a function argument type *)|CTFRes(* In a function result type *)|CTArray(* In an array type *)|CTPtr(* In a pointer type *)|CTExp(* In an expression, as the type of
the result of binary operators, or
in a cast *)|CTSizeof(* In a sizeof *)|CTDecl(* In a typedef, or a declaration *)|CTNumeric(* As an argument to __real__ or __imag__ *)letd_context()=functionCTStruct->text"CTStruct"|CTUnion->text"CTUnion"|CTFArg->text"CTFArg"|CTFRes->text"CTFRes"|CTArray->text"CTArray"|CTPtr->text"CTPtr"|CTExp->text"CTExp"|CTSizeof->text"CTSizeof"|CTDecl->text"CTDecl"|CTNumeric->text"CTNumeric"(* Keep track of all tags that we use. For each tag remember also the info
structure and a flag whether it was actually defined or just used. A
forward declaration acts as a definition. *)typedefuse=Defined(* We actually have seen a definition of this tag *)|Forward(* We have seen a forward declaration for it. This is done using
a GType with an empty type name *)|Used(* Only uses *)letcompUsed:(int,compinfo*defuseref)H.t=H.create117letenumUsed:(string,enuminfo*defuseref)H.t=H.create117lettypUsed:(string,typeinfo*defuseref)H.t=H.create117(* For composite types we also check that the names are unique *)letcompNames:(string,unit)H.t=H.create17lettypeSigIgnoreConst(t:typ):typsig=letattrFilter(attr:attribute):bool=matchattrwith|Attr("const",[])->false|Attr("pconst",[])->false|_->trueintypeSigWithAttrs(List.filterattrFilter)t(* Check a type *)letreccheckType(t:typ)(ctx:ctxType)=(* Check that it appears in the right context *)letreccheckContext=functionTVoid_->ctx=CTPtr||ctx=CTFRes||ctx=CTDecl||ctx=CTSizeof|TNamed(ti,a)->checkContextti.ttype|TArray_->(ctx=CTStruct||ctx=CTUnion||ctx=CTSizeof||ctx=CTDecl||ctx=CTArray||ctx=CTPtr)|TFun_->ctx=CTPtr||ctx=CTDecl||ctx=CTSizeof|TInt_->true|TFloat_->true|_->ctx<>CTNumericinifnot(checkContextt)thenignore(warn"Type (%a) used in wrong context. Expected context: %a"d_plaintypetd_contextctx);matchtwith(TVoida|TBuiltin_va_lista)->checkAttributesa|TInt(ik,a)->checkAttributesa|TFloat(_,a)->checkAttributesa;ifhasAttribute"complex"athenE.s(E.bug"float type has attribute complex, this should never be the case as there are fkinds for this");|TPtr(t,a)->checkAttributesa;checkTypetCTPtr|TNamed(ti,a)->checkAttributesa;ifti.tname=""thenignore(warnContext"Using a typeinfo for an empty-named type");checkTypeInfoUsedti|TComp(comp,a)->checkAttributesa;(* Mark it as a forward. We'll check it later. If we try to check it
now we might encounter undefined types *)checkCompInfoUsedcomp|TEnum(enum,a)->begincheckAttributesa;checkEnumInfoUsedenumend|TArray(bt,len,a)->checkAttributesa;checkTypebtCTArray;(matchlenwithNone->()|Somel->lett=typeOflinifnot(isIntegralTypet)thenE.s(bug"Type of array length is not integer"))|TFun(rt,targs,isva,a)->checkAttributesa;checkTypertCTFRes;List.iter(fun(an,at,aa)->checkTypeatCTFArg;checkAttributesaa)(argsToListtargs)(* Check that a type is a promoted integral type *)andcheckIntegralType(t:typ)=checkTypetCTExp;ifnot(isIntegralTypet)thenignore(warn"Non-integral type")(* Check that a type is a promoted arithmetic type *)andcheckArithmeticType(t:typ)=checkTypetCTExp;ifnot(isArithmeticTypet)thenignore(warn"Non-arithmetic type")(* Check that a type is a pointer type *)andcheckPointerType(t:typ)=checkTypetCTExp;ifnot(isPointerTypet)thenignore(warn"Non-pointer type")(* Check that a type is a scalar type *)andcheckScalarType(t:typ)=checkTypetCTExp;ifnot(isScalarTypet)thenignore(warn"Non-scalar type")andtypeMatch(t1:typ)(t2:typ)=if!Cil.insertImplicitCaststhenbegin(* Allow mismatches in const-ness, so that string literals can be used
as char*s *)iftypeSigIgnoreConstt1<>typeSigIgnoreConstt2thenmatchunrollTypet1,unrollTypet2with(* Allow free interchange of TInt and TEnum *)TInt(ik,_),TEnum(ei,_)whenik=ei.ekind->()|TEnum(ei,_),TInt(ik,_)whenik=ei.ekind->()(* Allow unspecified array lengths - this happens with
flexible array members *)|TArray(t,None,_),TArray(t',_,_)|TArray(t,_,_),TArray(t',None,_)->typeMatchtt'|_,_->ignore(warn"Type mismatch:@! %a@!and %a@!"d_typet1d_typet2)endelsebegin(* Many casts are missing. For now, just skip this check. *)endandcheckCompInfo(isadef:defuse)comp=letfullname=compFullNamecompintryletoldci,olddef=H.findcompUsedcomp.ckeyin(* Check that it is the same *)ifoldci!=compthenignore(warnContext"compinfo for %s not shared"fullname);(match!olddef,isadefwith|Defined,Defined->ignore(warnContext"Multiple definition of %s"fullname)|_,Defined->olddef:=Defined|Defined,_->()|_,Forward->olddef:=Forward|_,_->())withNot_found->begin(* This is the first time we see it *)(* Check that the name is not empty *)ifcomp.cname=""thenE.s(bug"Compinfo with empty name");(* Check that the name is unique *)ifH.memcompNamesfullnamethenignore(warn"Duplicate name %s"fullname);(* Add it to the map before we go on *)H.addcompUsedcomp.ckey(comp,refisadef);H.addcompNamesfullname();(* Do not check the compinfo unless this is a definition. Otherwise you
might run into undefined types. *)ifisadef=DefinedthenbegincheckAttributescomp.cattr;letfctx=ifcomp.cstructthenCTStructelseCTUnioninletcheckFieldf=ifnot(f.fcomp==comp&&(* Each field must share the self cell of
the host *)f.fname<>"")thenignore(warn"Self pointer not set in field %s of %s"f.fnamefullname);checkTypef.ftypefctx;(* Check the bitfields *)(matchunrollTypef.ftype,f.fbitfieldwith|TInt(ik,a),Somew->checkAttributesa;ifw<0||w>bitsSizeOf(TInt(ik,a))thenignore(warn"Wrong width (%d) in bitfield"w)|_,Somew->ignore(E.error"Bitfield on a non integer type")|_->());checkAttributesf.fattrinList.itercheckFieldcomp.cfieldsendendandcheckEnumInfo(isadef:defuse)enum=ifenum.ename=""thenE.s(bug"Enuminfo with empty name");tryletoldei,olddef=H.findenumUsedenum.enamein(* Check that it is the same *)ifoldei!=enumthenignore(warnContext"enuminfo for %s not shared"enum.ename);(match!olddef,isadefwithDefined,Defined->ignore(warnContext"Multiple definition of enum %s"enum.ename)|_,Defined->olddef:=Defined|Defined,_->()|_,Forward->olddef:=Forward|_,_->())withNot_found->begin(* This is the first time we see it *)(* Add it to the map before we go on *)H.addenumUsedenum.ename(enum,refisadef);checkAttributesenum.eattr;List.iter(fun(tn,attrs,_,_)->defineNametn;checkAttributesattrs)enum.eitems;endandcheckTypeInfo(isadef:defuse)ti=tryletoldti,olddef=H.findtypUsedti.tnamein(* Check that it is the same *)ifoldti!=tithenignore(warnContext"typeinfo for %s not shared"ti.tname);(match!olddef,isadefwithDefined,Defined->ignore(warnContext"Multiple definition of type %s"ti.tname)|Defined,Used->()|Used,Defined->ignore(warnContext"Use of type %s before its definition"ti.tname)|_,_->ignore(warnContext"Bug in checkTypeInfo for %s"ti.tname))withNot_found->begin(* This is the first time we see it *)ifti.tname=""thenignore(warnContext"typeinfo with empty name");checkTypeti.ttypeCTDecl;(* Add it to the map before we go on *)H.addtypUsedti.tname(ti,refisadef);end(* Check an lvalue. If isconst then the lvalue appears in a context where
only a compile-time constant can appear. Return the type of the lvalue.
See the typing rule from cil.mli *)andcheckLval(isconst:bool)(forAddrof:bool)(lv:lval):typ=matchlvwithVarvi,off->checkVariablevi;checkOffsetvi.vtypeoff|Memaddr,off->beginifisconst&¬forAddrofthenignore(warn"Memory operation in constant");letta=checkExpfalseaddrinmatchunrollTypetawithTPtr(t,_)->checkOffsettoff|_->E.s(bug"Mem on a non-pointer")end(* Check an offset. The basetype is the type of the object referenced by the
base. Return the type of the lvalue constructed from a base value of right
type and the offset. See the typing rules from cil.mli *)andcheckOffsetbasetyp:offset->typ=functionNoOffset->basetyp|Index(ei,o)->checkIntegralType(checkExpfalseei);beginmatchunrollTypebasetypwithTArray(t,_,_)->checkOffsetto|t->E.s(bug"typeOffset: Index on a non-array: %a"d_plaintypet)end|Field(fi,o)->(* Now check that the host is shared propertly *)checkCompInfoUsedfi.fcomp;(* Check that this exact field is part of the host *)ifnot(List.exists(funf->f==fi)fi.fcomp.cfields)thenignore(warn"Field %s not part of %s"fi.fname(compFullNamefi.fcomp));checkOffsetfi.ftypeoandcheckExpType(isconst:bool)(e:exp)(t:typ)=lett'=checkExpisconstein(* compute the type *)(* ignore(E.log "checkType %a %a\n" d_plainexp e d_plaintype t); *)typeMatcht't(* Check an expression. isconst specifies if the expression occurs in a
context where only a compile-time constant can occur. Return the computed
type of the expression *)andcheckExp(isconst:bool)(e:exp):typ=E.withContext(fun_->dprintf"check%s: %a"(ifisconstthen"Const"else"Exp")d_expe)(fun_->matchewith|Const(_)->typeOfe|Lval(lv)->ifisconstthenignore(warn"Lval in constant");checkLvalisconstfalselv|SizeOf(t)->begin(* Sizeof cannot be applied to certain types *)checkTypetCTSizeof;(matchunrollTypetwith(TFun_)->ignore(warn"Invalid operand for sizeof")|_->());typeOfeend|SizeOfE(e')->(* The expression in a sizeof can be anything *)lette=checkExpfalsee'incheckTypeteCTSizeof;typeOfe|SizeOfStrs->typeOfe|Reale->lette=checkExpisconsteintypeOfRealAndImagComponentste|Image->lette=checkExpisconsteintypeOfRealAndImagComponentste|AlignOf(t)->begin(* Sizeof cannot be applied to certain types *)checkTypetCTSizeof;typeOfeend|AlignOfE(e')->(* The expression in an AlignOfE can be anything *)lette=checkExpfalsee'incheckTypeteCTSizeof;typeOfe|UnOp(Neg,e,tres)->checkArithmeticTypetres;checkExpTypeisconstetres;tres|UnOp(BNot,e,tres)->checkIntegralTypetres;checkExpTypeisconstetres;tres|UnOp(LNot,e,tres)->lette=checkExpisconsteincheckScalarTypete;checkIntegralTypetres;(* Must check that t is well-formed *)typeMatchtresintType;tres|BinOp(bop,e1,e2,tres)->beginlett1=checkExpisconste1inlett2=checkExpisconste2inmatchbopwith(Mult|Div)->typeMatcht1t2;checkArithmeticTypetres;typeMatcht1tres;tres|(Eq|Ne|Lt|Le|Ge|Gt)->typeMatcht1t2;checkArithmeticTypet1;typeMatchtresintType;tres|Mod|BAnd|BOr|BXor->typeMatcht1t2;checkIntegralTypetres;typeMatcht1tres;tres|LAnd|LOr->checkScalarTypet1;checkScalarTypet2;typeMatchtresintType;tres|Shiftlt|Shiftrt->typeMatcht1tres;checkIntegralTypet1;checkIntegralTypet2;tres|(PlusA|MinusA)->typeMatcht1t2;typeMatcht1tres;checkArithmeticTypetres;tres|(PlusPI|MinusPI|IndexPI)->checkPointerTypetres;typeMatcht1tres;checkIntegralTypet2;tres|MinusPP->checkPointerTypet1;checkPointerTypet2;typeMatcht1t2;typeMatchtres!ptrdiffType;tresend|Question(e1,e2,e3,tres)->beginlett1=checkExpisconste1inlett2=checkExpisconste2inlett3=checkExpisconste3incheckScalarTypet1;typeMatcht2t3;typeMatcht2tres;tresend|AddrOf(lv)->beginlettlv=checkLvalisconsttruelvin(* Only certain types can be in AddrOf *)matchunrollTypetlvwith|TVoid_->E.s(bug"AddrOf on improper type");|(TInt_|TFloat_|TPtr_|TComp_|TFun_|TArray_)->TPtr(tlv,[])|TEnum(ei,_)->TPtr(TInt(ei.ekind,[]),[])|_->E.s(bug"AddrOf on unknown type")end|AddrOfLabel(gref)->begin(* Find a label *)letlab=matchList.filter(functionLabel_->true|_->false)!gref.labelswithLabel(lab,_,_)::_->lab|_->ignore(warn"Address of label to block without a label");"<missing label>"in(* Remember it as a target *)gotoTargets:=(lab,!gref)::!gotoTargets;voidPtrTypeend|StartOflv->beginlettlv=checkLvalisconsttruelvinmatchunrollTypetlvwithTArray(t,_,_)->TPtr(t,[])|_->E.s(bug"StartOf on a non-array")end|CastE(tres,e)->beginletet=checkExpisconsteincheckTypetresCTExp;(* Not all types can be cast *)matchunrollTypeetwithTArray_->E.s(bug"Cast of an array type")|TFun_->E.s(bug"Cast of a function type")(* A TComp cast that changes the attributes is okay. *)(* | TComp _ -> E.s (bug "Cast of a composite type") *)|TVoid_->E.s(bug"Cast of a void type")|_->tresend)()(* The argument of withContext *)andcheckInit(i:init):typ=E.withContext(fun_->dprintf"checkInit: %a"d_initi)(fun_->matchiwithSingleInite->checkExptruee(*
| ArrayInit (bt, len, initl) -> begin
checkType bt CTSizeof;
if List.length initl > len then
ignore (warn "Too many initializers in array");
List.iter (fun i -> checkInitType i bt) initl;
TArray(bt, Some (integer len), [])
end
*)|CompoundInit(ct,initl)->begincheckTypectCTSizeof;(matchunrollTypectwithTArray(bt,elen,_)->letlen=matchelenwith|None->0L|Somee->(ignore(checkExptruee);matchgetInteger(constFoldtruee)withSomelen->Z.to_int64len(* Z on purpose, we don't want to ignore overflows here *)|None->ignore(warn"Array length is not a constant");0L)inletrecloopIndexi=function[]->ifi>lenthenignore(warn"Wrong number of initializers in array")|(Index(Const(CInt(i',_,_)),NoOffset),ei)::rest->ifInt64.compare(Z.to_int64i')i<>0thenignore(warn"Initializer for index %s when %s was expected"(Printf.sprintf"%Ld"(Z.to_int64i'))(Printf.sprintf"%Ld"i));checkInitTypeeibt;loopIndex(Int64.succi)rest|_::rest->ignore(warn"Malformed initializer for array element")inloopIndexInt64.zeroinitl|TComp(comp,_)->ifcomp.cstructthenletrecloopFields(nextflds:fieldinfolist)(initl:(offset*init)list):unit=matchnextflds,initlwith[],[]->()(* We are done *)|f::restf,(Field(f',NoOffset),i)::resti->iff.fname<>f'.fnamethenignore(warn"Expected initializer for field %s and found one for %s"f.fnamef'.fname);checkInitTypeif.ftype;loopFieldsrestfresti|[],_::_->ignore(warn"Too many initializers for struct")|_::_,[]->ignore(warn"Too few initializers for struct")|_,_->ignore(warn"Malformed initializer for struct")inloopFields(List.filter(funf->f.fname<>missingFieldName)comp.cfields)initlelse(* UNION *)ifcomp.cfields==[]thenbeginifinitl!=[]thenignore(warn"Initializer for empty union not empty");endelsebeginmatchinitlwith[(Field(f,NoOffset),ei)]->iff.fcomp!=compthenignore(bug"Wrong designator for union initializer");checkInitTypeeif.ftype|_->ignore(warn"Malformed initializer for union")end|_->E.s(warn"Type of Compound is not array or struct or union"));ctend)()(* The arguments of withContext *)andcheckInitType(i:init)(t:typ):unit=letit=checkInitiintypeMatchittandcheckStmt(s:stmt)=E.withContext(fun_->(* Print context only for certain small statements *)matchs.skindwithLoop_|If_|Switch_->nil|_->dprintf"checkStmt: %a"d_stmts)(fun_->(* Check the labels *)letcheckLabel=functionLabel(ln,l,_)->ifH.memlabelslnthenignore(warn"Multiply defined label %s"ln);H.addlabelsln()|Case(e,_,_)->lett=checkExptrueeinifnot(isIntegralTypet)thenE.s(bug"Type of case expression is not integer");|CaseRange(e1,e2,_,_)->lett1=checkExptruee1inifnot(isIntegralTypet1)thenE.s(bug"Type of case expression is not integer");lett2=checkExptruee2inifnot(isIntegralTypet2)thenE.s(bug"Type of case expression is not integer");|_->()(* Not yet implemented *)inList.itercheckLabels.labels;(* See if we have seen this statement before *)ifList.memqs!statementsthenignore(warn"Statement is shared");(* Remember that we have seen this one *)statements:=s::!statements;matchs.skindwithBreak_|Continue_->()|Goto(gref,l)->currentLoc:=l;(* Find a label *)letlab=matchList.filter(functionLabel_->true|_->false)!gref.labelswithLabel(lab,_,_)::_->lab|_->ignore(warn"Goto to block without a label");"<missing label>"in(* Remember it as a target *)gotoTargets:=(lab,!gref)::!gotoTargets|ComputedGoto(e,l)->currentLoc:=l;lette=checkExpfalseeintypeMatchtevoidPtrType|Return(re,l,el)->begincurrentLoc:=l;currentExpLoc:=el;matchre,!currentReturnTypewithNone,TVoid_->()|_,TVoid_->ignore(warn"Invalid return value")|None,_->ignore(warn"Invalid return value")|Somere',rt'->checkExpTypefalsere'rt'end|Loop(b,l,el,_,_)->checkBlockb|Blockb->checkBlockb|If(e,bt,bf,l,el)->currentLoc:=l;currentExpLoc:=el;lette=checkExpfalseeincheckScalarTypete;checkBlockbt;checkBlockbf|Switch(e,b,cases,l,el)->currentLoc:=l;currentExpLoc:=el;lett=checkExpfalseeinifnot(isIntegralTypet)thenE.s(bug"Type of switch expression is not integer");(* Remember the statements so far *)letprevStatements=!statementsincheckBlockb;(* Now make sure that all the cases do occur in that block,
and that no case is listed twice. *)letcasesVisited:stmtlistref=ref[]inList.iter(func->(ifList.memqc!casesVisitedthenignore(warnContext"Duplicate stmt in \"cases\" list of Switch.")elsecasesVisited:=c::!casesVisited);(* Make sure it is in there *)letrecfindCase=function|lwhenl==prevStatements->(* Not found *)ignore(warnContext"Cannot find target of switch statement")|[]->E.s(E.bug"Check: findCase")|c'::restwhenc==c'->()(* Found *)|_::rest->findCaserestinfindCase!statements)cases;|Instril->List.itercheckInstril)()(* argument of withContext *)andcheckBlock(b:block):unit=List.itercheckStmtb.bstmtsandcheckInstr(i:instr)=if!ignoreInstrithen()elsematchiwith|Set(dest,e,l,el)->currentLoc:=l;currentExpLoc:=el;lett=checkLvalfalsefalsedestin(* Not all types can be assigned to *)(matchunrollTypetwithTFun_->ignore(warn"Assignment to a function type")|TArray_->ignore(warn"Assignment to an array type")|TVoid_->ignore(warn"Assignment to a void type")|_->());checkExpTypefalseet|Call(dest,what,args,l,el)->currentLoc:=l;currentExpLoc:=el;let(rt,formals,isva,fnAttrs)=matchunrollType(checkExpfalsewhat)withTFun(rt,formals,isva,fnAttrs)->rt,formals,isva,fnAttrs|_->E.s(bug"Call to a non-function")in(* Now check the return value*)(matchdest,unrollTypertwithNone,TVoid_->()(* Avoid spurious warnings for atomic builtins *)|Some_,TVoid[Attr("overloaded",[])]->()|Some_,TVoid_->ignore(warn"void value is assigned")|None,_->()(* "Call of function is not assigned" *)|Somedestlv,rt'->letdesttyp=checkLvalfalsefalsedestlviniftypeSigdesttyp<>typeSigrtthenbeginifnot!Cabs2cil.doCollapseCallCastthenignore(warn"Destination of Call does not match the return type.");(* Not all types can be assigned to *)(matchunrollTypedesttypwithTFun_->ignore(warn"Assignment to a function type")|TArray_->ignore(warn"Assignment to an array type")|TVoid_->ignore(warn"Assignment to a void type")|_->());(* Not all types can be cast *)(matchunrollTypert'withTArray_->ignore(warn"Cast of an array type")|TFun_->ignore(warn"Cast of a function type")|TComp_->ignore(warn"Cast of a composite type")|TVoid_->ignore(warn"Cast of a void type")|_->())end);(* Now check the arguments *)letrecloopArgsformalsargs=matchformals,argswith[],_when(isva||args=[])->()|(fn,ft,_)::formals,a::args->checkExpTypefalseaft;loopArgsformalsargs|_,_->ignore(warn"Not enough arguments")inifformals<>NonethenloopArgs(argsToListformals)args|VarDecl(v,_)->ifnotv.vhasdeclinstructionthenE.s(bug"Encountered a VarDecl, but vhasdeclinstruction for the varinfo is not set")|Asm_->()(* Not yet implemented *)letreccheckGlobal=functionGAsm_->()|GPragma_->()|GText_->()|GType(ti,l)->currentLoc:=l;E.withContext(fun_->dprintf"GType(%s)"ti.tname)(fun_->checkTypeInfoDefinedti;ifti.tname<>""thendefineNameti.tname)()|GCompTag(comp,l)->currentLoc:=l;checkCompInfoDefinedcomp;|GCompTagDecl(comp,l)->currentLoc:=l;checkCompInfoForwardcomp;|GEnumTag(enum,l)->currentLoc:=l;checkEnumInfoDefinedenum|GEnumTagDecl(enum,l)->currentLoc:=l;checkEnumInfoForwardenum|GVarDecl(vi,l)->currentLoc:=l;(* We might have seen it already *)E.withContext(fun_->dprintf"GVarDecl(%s)"vi.vname)(fun_->(* If we have seen this vid already then it must be for the exact
same varinfo *)ifH.memvarIdsEnvvi.vidthencheckVariablevielsebegindefineVariablevi;checkAttributesvi.vattr;checkTypevi.vtypeCTDecl;ifnot(vi.vglob&&vi.vstorage<>Register)thenE.s(bug"Invalid declaration of %s"vi.vname)end)()|GVar(vi,init,l)->currentLoc:=l;(* Maybe this is the first occurrence *)E.withContext(fun_->dprintf"GVar(%s)"vi.vname)(fun_->checkGlobal(GVarDecl(vi,l));(* Check the initializer *)ifvi.vinit!=initthenE.s(bug"GVar initializer doesn't match vinit (%s)"vi.vname);beginmatchinit.initwithNone->()|Somei->ignore(checkInitTypeivi.vtype)end;(* Cannot be a function *)ifisFunctionTypevi.vtypethenE.s(bug"GVar for a function (%s)\n"vi.vname);)()|GFun(fd,l)->begincurrentLoc:=l;(* Check if this is the first occurrence *)letvi=fd.svarinletfname=vi.vnameinifH.memfundecForVarIdsvi.vidthenignore(warn"There already is a different fundec for vid %d (%s)"vi.vidvi.vname);E.withContext(fun_->dprintf"GFun(%s)"fname)(fun_->checkGlobal(GVarDecl(vi,l));(* Check that the argument types in the type are identical to the
formals *)letrecloopArgstargsformals=matchtargs,formalswith[],[]->()|(fn,ft,fa)::targs,fo::formals->iffn<>fo.vnamethenignore(warnContext"Formal %s not shared (expecting name %s) in %s"fo.vnamefnfname);E.withContext(fun()->text"formal "++textfo.vname)(fun()->typeMatchftfo.vtype)();iffa!=fo.vattrthenignore(warnContext"Formal %s not shared (different attrs) in %s"fo.vnamefname);loopArgstargsformals|_->E.s(bug"Type has different number of formals for %s"fname)inbeginmatchunrollTypevi.vtypewithTFun(rt,args,isva,a)->begincurrentReturnType:=rt;loopArgs(argsToListargs)fd.sformalsend|_->E.s(bug"Function %s does not have a function type"fname)end;ignore(fd.smaxid>=0||E.s(bug"smaxid < 0 for %s"fname));(* Now start a new environment, in a finally clause *)begintrystartEnv();(* Do the locals *)letdoLocaltctxv=ifv.vglobthenignore(warnContext"Local %s has the vglob flag set"v.vname);ifv.vstorage<>NoStorage&&v.vstorage<>Register&&v.vstorage<>Staticthenignore(warnContext"Local %s has storage %a\n"v.vnamed_storagev.vstorage);checkTypev.vtypetctx;checkAttributesv.vattr;defineVariablevinList.iter(doLocalCTFArg)fd.sformals;List.iter(doLocalCTDecl)fd.slocals;statements:=[];gotoTargets:=[];checkBlockfd.sbody;H.clearlabels;(* Now verify that we have scanned all targets *)List.iter(fun(lab,t)->ifnot(List.memqt!statements)thenignore(warnContext"Target of \"goto %s\" statement does not appear in function body"lab))!gotoTargets;statements:=[];gotoTargets:=[];(* Done *)endEnv()withe->endEnv();raiseeend;())()(* final argument of withContext *)endletcheckFileflagsfl=if!E.verboseFlagthenignore(E.log"Checking file %s\n"fl.fileName);valid:=true;List.iter(functionNoCheckGlobalIds->checkGlobalIds:=false|IgnoreInstructionsf->ignoreInstr:=f)flags;iterGlobalsfl(fung->trycheckGlobalgwith_->());(* Check that for all struct/union tags there is a definition *)H.iter(funk(comp,isadef)->if!isadef=Usedthenbeginvalid:=false;ignore(E.warn"Compinfo %s is referenced but not defined"(compFullNamecomp))end)compUsed;(* Check that for all enum tags there is a definition *)H.iter(funk(enum,isadef)->if!isadef=Usedthenbeginvalid:=false;ignore(E.warn"Enuminfo %s is referenced but not defined"enum.ename)end)enumUsed;(* Clean the hashes to let the GC do its job *)H.cleartypeDefs;H.clearvarNamesEnv;H.clearvarIdsEnv;H.clearallVarIds;H.clearfundecForVarIds;H.clearcompNames;H.clearcompUsed;H.clearenumUsed;H.cleartypUsed;varNamesList:=[];if!E.verboseFlagthenignore(E.log"Finished checking file %s\n"fl.fileName);!validletcheckStandaloneExp~(vars:varinfolist)(exp:exp)=if!E.verboseFlagthenignore(E.log"Checking exp %a\n"d_expexp);valid:=true;List.iterdefineVariablevars;(tryignore(checkExpfalseexp)with_->());(* Clean the hashes to let the GC do its job *)H.cleartypeDefs;H.clearvarNamesEnv;H.clearvarIdsEnv;H.clearallVarIds;H.clearfundecForVarIds;H.clearcompNames;H.clearcompUsed;H.clearenumUsed;H.cleartypUsed;varNamesList:=[];if!E.verboseFlagthenignore(E.log"Finished checking exp %a\n"d_expexp);!valid