123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392(*
Copyright (c) 2001-2002,
John Kodumal <jkodumal@eecs.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.
*)openGoblintCil(***********************************************************************)(* *)(* *)(* This file is currently unused by CIL. It is included in the *)(* distribution for reference only. *)(* *)(* *)(***********************************************************************)(***********************************************************************)(* *)(* Type Declarations *)(* *)(***********************************************************************)exceptionInconsistentofstringexceptionNo_contentsexceptionBad_projexceptionBad_type_copymoduleU=UrefmoduleS=SetpmoduleH=HashtblmoduleQ=Queue(** Polarity kinds-- positive, negative, or nonpolar. *)typepolarity=Pos|Neg|Non(** Label bounds. The polymorphic type is a hack for recursive modules *)type'abound={index:int;info:'a}(** The 'a type may in general contain urefs, which makes Stdlib.compare
incorrect. However, the bounds will always be correct because if two tau's
get unified, their cached instantiations will be re-entered into the
worklist, ensuring that any labels find the new bounds *)moduleBound=structtype'at='aboundletcompare(x:'at)(y:'at)=Stdlib.comparexyendmoduleB=S.Make(Bound)type'aboundset='aB.t(** Constants, which identify elements in points-to sets *)typeconstant=int*stringmoduleConstant=structtypet=constantletcompare((xid,_):t)((yid,_):t)=Stdlib.comparexidyidendmoduleC=Set.Make(Constant)(** Sets of constants. Set union is used when two labels containing
constant sets are unified *)typeconstantset=C.ttypelblinfo={mutablel_name:string;(** Name of this label *)mutablealiases:constantset;(** Set of constants (tags) for checking aliases *)p_bounds:labelboundsetU.uref;(** Set of umatched (p) lower bounds *)n_bounds:labelboundsetU.uref;(** Set of unmatched (n) lower bounds *)mutablep_cached:bool;(** Flag indicating whether all reachable p edges have been locally cached *)mutablen_cached:bool;(** Flag indicating whether all reachable n edges have been locally cached *)mutableon_path:bool;(** For cycle detection during reachability queries *)}(** Constructor labels *)andlabel=lblinfoU.uref(** The type of lvalues. *)typelvalue={l:label;contents:tau}(** Data for variables. *)andvinfo={v_name:string;mutablev_global:bool;v_cache:cache}(** Data for ref constructors. *)andrinfo={rl:label;mutabler_global:bool;points_to:tau;r_cache:cache}(** Data for fun constructors. *)andfinfo={fl:label;mutablef_global:bool;args:taulistref;ret:tau;f_cache:cache}(* Data for pairs. Note there is no label. *)andpinfo={mutablep_global:bool;ptr:tau;lam:tau;p_cache:cache}(** Type constructors discovered by type inference *)andtinfo=|Varofvinfo|Refofrinfo|Funoffinfo|Pairofpinfo(** The top-level points-to type. *)andtau=tinfoU.uref(** The instantiation constraint cache. The index is used as a key. *)andcache=(int,polarity*tau)H.t(* Type of semi-unification constraints *)typesu_constraint=Instantiationoftau*(int*polarity)*tau|Unificationoftau*tau(** Association lists, used for printing recursive types. The first element
is a type that has been visited. The second element is the string
representation of that type (so far). If the string option is set, then
this type occurs within itself, and is associated with the recursive var
name stored in the option. When walking a type, add it to an association
list.
Example : suppose we have the constraint 'a = ref('a). The type is unified
via cyclic unification, and would loop infinitely if we attempted to print
it. What we want to do is print the type u rv. ref(rv). This is accomplished
in the following manner:
-- ref('a) is visited. It is not in the association list, so it is added
and the string "ref(" is stored in the second element. We recurse to print
the first argument of the constructor.
-- In the recursive call, we see that 'a (or ref('a)) is already in the
association list, so the type is recursive. We check the string option,
which is None, meaning that this is the first recurrence of the type. We
create a new recursive variable, rv and set the string option to 'rv. Next,
we prepend u rv. to the string representation we have seen before, "ref(",
and return "rv" as the string representation of this type.
-- The string so far is "u rv.ref(". The recursive call returns, and we
complete the type by printing the result of the call, "rv", and ")"
In a type where the recursive variable appears twice, e.g. 'a = pair('a,'a),
the second time we hit 'a, the string option will be set, so we know to
reuse the same recursive variable name.
*)typeassociation=tau*stringref*stringoptionref(***********************************************************************)(* *)(* Global Variables *)(* *)(***********************************************************************)(** Print the instantiations constraints (loops with cyclic structures). *)letprint_constraints:boolref=reffalse(** Solve constraints as they are introduced. If this is false, constraints
are solved in batch fashion at calls to solveConstraints. *)letsolve_online:boolref=reftrue(** If true, print all constraints (including induced) and show additional
debug output. *)letdebug=reffalseletdebug_constraints=debug(** If true, print out extra verbose debug information (including contents
of label sets *)letverbose_debug=reffalse(** If true, make the flow step a no-op *)letno_flow=reffalseletno_sub=reffalse(** If true, do not add instantiation constraints *)letanalyze_mono=reffalse(** A counter for generating unique integers. *)letcounter:intref=ref0(** A list of equality constraints. *)leteq_worklist:su_constraintQ.t=Q.create()(** A list of instantiation constraints. *)letinst_worklist:su_constraintQ.t=Q.create()(***********************************************************************)(* *)(* Utility Functions *)(* *)(***********************************************************************)(** Consistency check for inferred types *)letpair_or_var(t:tau)=match(U.dereft)with|Pair_->true|Var_->true|_->falseletref_or_var(t:tau)=match(U.dereft)with|Ref_->true|Var_->true|_->falseletfun_or_var(t:tau)=match(U.dereft)with|Fun_->true|Var_->true|_->false(** Generate a unique integer. *)letfresh_index():int=incrcounter;!counter(** Negate a polarity. *)letnegate(p:polarity):polarity=matchpwith|Pos->Neg|Neg->Pos|Non->Non(** Compute the least-upper-bounds of two polarities. *)letlub(p,p':polarity*polarity):polarity=matchpwith|Pos->beginmatchp'with|Pos->Pos|_->Nonend|Neg->beginmatchp'with|Neg->Neg|_->Nonend|Non->Non(** Extract the cache from a type *)letget_cache(t:tau):cache=matchU.dereftwith|Varv->v.v_cache|Refr->r.r_cache|Pairp->p.p_cache|Funf->f.f_cache(** Determine whether or not a type is global *)letget_global(t:tau):bool=matchU.dereftwith|Varv->v.v_global|Refr->r.r_global|Pairp->p.p_global|Funf->f.f_global(** Return true if a type is monomorphic (global). *)letglobal_tau=get_globalletglobal_lvaluelv=get_globallv.contents(** Return true if e is a member of l (according to uref equality) *)letreculist_memel=matchlwith|[]->false|h::t->if(U.equal(h,e))thentrueelseulist_memet(** Convert a polarity to a string *)letstring_of_polarityp=matchpwith|Pos->"+"|Neg->"-"|Non->"T"(** Convert a label to a string, short representation *)letstring_of_label2(l:label):string="\""^(U.derefl).l_name^"\""(** Convert a label to a string, long representation *)letstring_of_label(l:label):string=letrecconstset_to_string=function|(_,s)::[]->s|(_,s)::t->s^","^(constset_to_stringt)|[]->""inletaliases=constset_to_string(C.elements((U.derefl).aliases))inif((aliases="")||(not!verbose_debug))thenstring_of_label2lelsealiases(** Return true if the element [e] is present in the association list *)letrecassoc_list_mem(e:tau)(l:associationlist)=matchlwith|[]->None|(h,s,so)::t->if(U.equal(h,e))then(Some(s,so))elseassoc_list_memet(** Given a tau, create a unique recursive variable name. This should always
return the same name for a given tau *)letfresh_recvar_name(t:tau):string=matchU.dereftwith|Pairp->"rvp"^string_of_int((Hashtbl.hashp))|Refr->"rvr"^string_of_int((Hashtbl.hashr))|Funf->"rvf"^string_of_int((Hashtbl.hashf))|_->raise(Inconsistent("recvar_name"))(** Return a string representation of a tau, using association lists. *)letstring_of_tau(t:tau):string=lettau_map:associationlistref=ref[]inletrecstring_of_tau't=match(assoc_list_memt(!tau_map))with|Some(s,so)->(* recursive type. see if a var name has been set *)beginmatch(!so)with|None->beginletrv=fresh_recvar_name(t)ins:="u "^rv^"."^(!s);so:=Some(rv);rvend|Somerv->rvend|None->(* type's not recursive. Add it to the assoc list and cont. *)lets=ref""inletso:stringoptionref=refNoneinbegintau_map:=(t,s,so)::(!tau_map);(match(U.dereft)with|Varv->s:=v.v_name;|Pairp->beginassert(ref_or_var(p.ptr));assert(fun_or_var(p.lam));s:="{";s:=(!s)^(string_of_tau'p.ptr);s:=(!s)^",";s:=(!s)^(string_of_tau'p.lam);s:=(!s)^"}"end|Refr->beginassert(pair_or_var(r.points_to));s:="ref(|";s:=(!s)^(string_of_labelr.rl);s:=(!s)^"|,";s:=(!s)^(string_of_tau'r.points_to);s:=(!s)^")"end|Funf->beginassert(pair_or_var(f.ret));letrecstring_of_args=function|h::[]->beginassert(pair_or_var(h));s:=(!s)^(string_of_tau'h)end|h::t->beginassert(pair_or_var(h));s:=(!s)^(string_of_tau'h)^",";string_of_argstend|[]->()ins:="fun(|";s:=(!s)^(string_of_labelf.fl);s:=(!s)^"|,";s:=(!s)^"<";if(List.length!(f.args)>0)thenstring_of_args!(f.args)elses:=(!s)^"void";s:=(!s)^">,";s:=(!s)^(string_of_tau'f.ret);s:=(!s)^")"end);tau_map:=List.tl(!tau_map);!sendinstring_of_tau't(** Convert an lvalue to a string *)letstring_of_lvalue(lv:lvalue):string=letcontents=(string_of_tau(lv.contents))inletl=(string_of_labellv.l)inassert(pair_or_var(lv.contents));Printf.sprintf"[%s]^(%s)"contentsl(** Print a constraint. *)letprint_constraint(c:su_constraint)=matchcwith|Unification(t,t')->letlhs=string_of_tautinletrhs=string_of_taut'inPrintf.printf"%s == %s\n"lhsrhs|Instantiation(t,(i,p),t')->letlhs=string_of_tautinletrhs=string_of_taut'inletindex=string_of_intiinletpol=string_of_polaritypinPrintf.printf"%s <={%s,%s} %s\n"lhsindexpolrhs(* If [positive] is true, return the p-edge bounds, otherwise, return
the n-edge bounds. *)letget_bounds(positive:bool)(l:label):labelboundsetU.uref=if(positive)then(U.derefl).p_boundselse(U.derefl).n_bounds(** Used for cycle detection during the flow step. Returns true if the
label [l] is found on the current path. *)leton_path(l:label):bool=(U.derefl).on_path(** Used for cycle detection during the flow step. Identifies [l] as being
on/off the current path. *)letset_on_path(l:label)(b:bool):unit=(U.derefl).on_path<-b(** Make the type a global type *)letset_global(t:tau)(b:bool):bool=if(!debug&&b)thenPrintf.printf"Setting a new global : %s\n"(string_of_taut);beginassert((not(get_global(t)))||b);(matchU.dereftwith|Varv->v.v_global<-b|Refr->r.r_global<-b|Pairp->p.p_global<-b|Funf->f.f_global<-b);bend(** Return a label's bounds as a string *)letstring_of_bounds(is_pos:bool)(l:label):string=letbounds=if(is_pos)thenU.deref((U.derefl).p_bounds)elseU.deref((U.derefl).n_bounds)inB.fold(funb->funres->res^(string_of_label2b.info)^" ")bounds""(***********************************************************************)(* *)(* Type Operations -- these do not create any constraints *)(* *)(***********************************************************************)(** Create an lvalue with label [lbl] and tau contents [t]. *)letmake_lval(lbl,t:label*tau):lvalue={l=lbl;contents=t}(** Create a new label with name [name]. Also adds a fresh constant
with name [name] to this label's aliases set. *)letmake_label(name:string):label=U.uref{l_name=name;aliases=(C.add(fresh_index(),name)C.empty);p_bounds=U.uref(B.empty);n_bounds=U.uref(B.empty);p_cached=false;n_cached=false;on_path=false}(** Create a new label with an unspecified name and an empty alias set. *)letfresh_label():label=U.uref{l_name="l_"^(string_of_int(fresh_index()));aliases=(C.empty);p_bounds=U.uref(B.empty);n_bounds=U.uref(B.empty);p_cached=false;n_cached=false;on_path=false}(** Create a fresh bound. *)letmake_bound(i,a:int*'a):'abound={index=i;info=a}(** Create a fresh named variable with name '[name]. *)letmake_var(b:bool)(name:string):tau=U.uref(Var{v_name=("'"^name);v_global=b;v_cache=H.create4})(** Create a fresh unnamed variable (name will be 'fv). *)letfresh_var():tau=make_varfalse("fv"^(string_of_int(fresh_index())))(** Create a fresh unnamed variable (name will be 'fi). *)letfresh_var_i():tau=make_varfalse("fi"^(string_of_int(fresh_index())))(** Create a Fun constructor. *)letmake_fun(lbl,a,r:label*(taulist)*tau):tau=U.uref(Fun{fl=lbl;f_global=false;args=refa;ret=r;f_cache=H.create4})(** Create a Ref constructor. *)letmake_ref(lbl,pt:label*tau):tau=U.uref(Ref{rl=lbl;r_global=false;points_to=pt;r_cache=H.create4})(** Create a Pair constructor. *)letmake_pair(p,f:tau*tau):tau=U.uref(Pair{ptr=p;p_global=false;lam=f;p_cache=H.create4})(** Copy the toplevel constructor of [t], putting fresh variables in each
argument of the constructor. *)letcopy_toplevel(t:tau):tau=matchU.dereftwith|Pair_->make_pair(fresh_var_i(),fresh_var_i())|Ref_->make_ref(fresh_label(),fresh_var_i())|Funf->letfresh_fn=fun_->fresh_var_i()inmake_fun(fresh_label(),Util.list_mapfresh_fn!(f.args),fresh_var_i())|_->raiseBad_type_copyletpad_args(l,l':(taulistref)*(taulistref)):unit=letpadding=ref((List.length(!l))-(List.length(!l')))inif(!padding==0)then()elseletto_pad=if(!padding>0)thenl'else(padding:=-(!padding);l)infor_=1to(!padding)doto_pad:=(!to_pad)@[fresh_var()]done(***********************************************************************)(* *)(* Constraint Generation/ Resolution *)(* *)(***********************************************************************)(** Returns true if the constraint has no effect, i.e. either the left-hand
side or the right-hand side is wild. *)letwild_constraint(t,t':tau*tau):bool=letti,ti'=U.dereft,U.dereft'inmatchti,ti'with|_->falseexceptionCycle_found(** Cycle detection between instantiations. Returns true if there is a cycle
from t to t' *)letexists_cycle(t,t':tau*tau):bool=letvisited:taulistref=ref[]inletrecexists_cycle't=if(ulist_memt(!visited))thenbegin(*
print_string "Instantiation cycle found :";
print_tau_list (!visited);
print_newline();
print_string (string_of_tau t);
print_newline(); *)(* raise Instantiation_cycle *)(* visited := List.tl (!visited) *)(* check *)endelsebeginvisited:=t::(!visited);if(U.equal(t,t'))thenraiseCycle_foundelseH.iter(fun_->fun(_,t'')->if(U.equal(t,t''))then()elseignore(exists_cycle't''))(get_cachet);visited:=List.tl(!visited)endintryexists_cycle't;falsewith|Cycle_found->trueexceptionSubterm(** Returns true if [t'] is a proper subterm of [t] *)letproper_subterm(t,t')=letvisited:taulistref=ref[]inletrecproper_subterm't=if(ulist_memt(!visited))then()(* recursive type *)elseif(U.equal(t,t'))thenraiseSubtermelsebeginvisited:=t::(!visited);(match(U.dereft)with|Var_->()|Refr->proper_subterm'r.points_to|Pairp->proper_subterm'p.ptr;proper_subterm'p.lam|Funf->proper_subterm'f.ret;List.iter(proper_subterm')!(f.args));visited:=List.tl(!visited)endintryif(U.equal(t,t'))thenfalseelsebeginproper_subterm't;falseendwith|Subterm->true(** The extended occurs check. Search for a cycle of instantiations from [t]
to [t']. If such a cycle exists, check to see that [t'] is a proper subterm
of [t]. If it is, then return true *)leteoc(t,t'):bool=if(exists_cycle(t,t')&&proper_subterm(t,t'))thenbeginif(!debug)thenPrintf.printf"Occurs check : %s occurs within %s\n"(string_of_taut')(string_of_taut)else();trueendelsefalse(** Resolve an instantiation constraint *)letrecinstantiate_int(t,(i,p),t':tau*(int*polarity)*tau)=if(wild_constraint(t,t')||(not(store(t,(i,p),t')))||U.equal(t,t'))then()elseletti,ti'=U.dereft,U.dereft'inmatchti,ti'with|Refr,Refr'->instantiate_ref(r,(i,p),r')|Funf,Funf'->instantiate_fun(f,(i,p),f')|Pairpr,Pairpr'->beginadd_constraint_int(Instantiation(pr.ptr,(i,p),pr'.ptr));add_constraint_int(Instantiation(pr.lam,(i,p),pr'.lam))end|Varv,_->()|_,Varv'->ifeoc(t,t')thenadd_constraint_int(Unification(t,t'))elsebeginunstore(t,i);add_constraint_int(Unification((copy_toplevelt),t'));add_constraint_int(Instantiation(t,(i,p),t'))end|_->raise(Inconsistent("instantiate"))(** Apply instantiations to the ref's label, and structurally down the type.
Contents of ref constructors are instantiated with polarity Non. *)andinstantiate_ref(ri,(i,p),ri'):unit=add_constraint_int(Instantiation(ri.points_to,(i,Non),ri'.points_to));instantiate_label(ri.rl,(i,p),ri'.rl)(** Apply instantiations to the fun's label, and structurally down the type.
Flip the polarity for the function's args. If the lengths of the argument
lists don't match, extend the shorter list as necessary. *)andinstantiate_fun(fi,(i,p),fi'):unit=pad_args(fi.args,fi'.args);assert(List.length!(fi.args)==List.length!(fi'.args));add_constraint_int(Instantiation(fi.ret,(i,p),fi'.ret));List.iter2(funt->funt'->add_constraint_int(Instantiation(t,(i,negatep),t')))!(fi.args)!(fi'.args);instantiate_label(fi.fl,(i,p),fi'.fl)(** Instantiate a label. Update the label's bounds with new flow edges.
*)andinstantiate_label(l,(i,p),l':label*(int*polarity)*label):unit=if(!debug)thenPrintf.printf"%s <= {%d,%s} %s\n"(string_of_labell)i(string_of_polarityp)(string_of_labell');letli,li'=U.derefl,U.derefl'inmatchpwith|Pos->U.update(li'.p_bounds,B.add(make_bound(i,l))(U.derefli'.p_bounds))|Neg->U.update(li.n_bounds,B.add(make_bound(i,l'))(U.derefli.n_bounds))|Non->beginU.update(li'.p_bounds,B.add(make_bound(i,l))(U.derefli'.p_bounds));U.update(li.n_bounds,B.add(make_bound(i,l'))(U.derefli.n_bounds))end(** Resolve a unification constraint. Does the uref unification after grabbing
a copy of the information before the two infos are unified. The other
interesting feature of this function is the way 'globalness' is propagated.
If a non-global is unified with a global, the non-global becomes global.
If the ecr became global, there is a problem because none of its cached
instantiations know that the type became monomorphic. In this case, they
must be re-inserted via merge-cache. Merge-cache always reinserts cached
instantiations from the non-ecr type, i.e. the type that was 'killed' by the
unification. *)andunify_int(t,t':tau*tau):unit=if(wild_constraint(t,t')||U.equal(t,t'))then()elseletti,ti'=U.dereft,U.dereft'inbeginU.unifycombine(t,t');matchti,ti'with|Varv,_->beginif(set_globalt'(v.v_global||(get_globalt')))then(H.iter(merge_cachet')(get_cachet'))else();H.iter(merge_cachet')v.v_cacheend|_,Varv->beginif(set_globalt(v.v_global||(get_globalt)))then(H.iter(merge_cachet)(get_cachet))else();H.iter(merge_cachet)v.v_cacheend|Refr,Refr'->beginif(set_globalt(r.r_global||r'.r_global))then(H.iter(merge_cachet)(get_cachet))else();H.iter(merge_cachet)r'.r_cache;unify_ref(r,r')end|Funf,Funf'->beginif(set_globalt(f.f_global||f'.f_global))then(H.iter(merge_cachet)(get_cachet))else();H.iter(merge_cachet)f'.f_cache;unify_fun(f,f');end|Pairp,Pairp'->beginif(set_globalt(p.p_global||p'.p_global))then(H.iter(merge_cachet)(get_cachet))else();H.iter(merge_cachet)p'.p_cache;add_constraint_int(Unification(p.ptr,p'.ptr));add_constraint_int(Unification(p.lam,p'.lam))end|_->raise(Inconsistent("unify"))end(** Unify the ref's label, and apply unification structurally down the type. *)andunify_ref(ri,ri':rinfo*rinfo):unit=add_constraint_int(Unification(ri.points_to,ri'.points_to));unify_label(ri.rl,ri'.rl)(** Unify the fun's label, and apply unification structurally down the type,
at arguments and return value. When combining two lists of different lengths,
always choose the longer list for the representative. *)andunify_fun(li,li':finfo*finfo):unit=letrecunion_args=function|_,[]->false|[],_->true|h::t,h'::t'->add_constraint_int(Unification(h,h'));union_args(t,t')inbeginunify_label(li.fl,li'.fl);add_constraint_int(Unification(li.ret,li'.ret));if(union_args(!(li.args),!(li'.args)))thenli.args:=!(li'.args);end(** Unify two labels, combining the set of constants denoting aliases. *)andunify_label(l,l':label*label):unit=letpick_name(li,li':lblinfo*lblinfo)=if((String.lengthli.l_name)>1&&(String.sub(li.l_name)02)="l_")thenli.l_name<-li'.l_nameelse()inletcombine_label(li,li':lblinfo*lblinfo):lblinfo=letp_bounds=U.deref(li.p_bounds)inletp_bounds'=U.deref(li'.p_bounds)inletn_bounds=U.deref(li.n_bounds)inletn_bounds'=U.deref(li'.n_bounds)inbeginpick_name(li,li');li.aliases<-C.union(li.aliases)(li'.aliases);U.update(li.p_bounds,(B.unionp_boundsp_bounds'));U.update(li.n_bounds,(B.unionn_boundsn_bounds'));liendin(*
if (!debug) then
begin
Printf.printf "Unifying %s with %s...\n"
(string_of_label l) (string_of_label l');
Printf.printf "pbounds : %s\n" (string_of_bounds true l);
Printf.printf "nbounds : %s\n" (string_of_bounds false l);
Printf.printf "pbounds : %s\n" (string_of_bounds true l');
Printf.printf "nbounds : %s\n\n" (string_of_bounds false l')
end; *)U.unifycombine_label(l,l')(* if (!debug) then
begin
Printf.printf "pbounds : %s\n" (string_of_bounds true l);
Printf.printf "nbounds : %s\n" (string_of_bounds false l)
end *)(** Re-assert a cached instantiation constraint, since the old type was
killed by a unification *)andmerge_cache(rep:tau)(i:int)(p,t':polarity*tau):unit=add_constraint_int(Instantiation(rep,(i,p),t'))(** Pick the representative info for two tinfo's. This function prefers the
first argument when both arguments are the same structure, but when
one type is a structure and the other is a var, it picks the structure. *)andcombine(ti,ti':tinfo*tinfo):tinfo=matchti,ti'with|Var_,_->ti'|_,_->ti(** Add a new constraint induced by other constraints. *)andadd_constraint_int(c:su_constraint)=if(!print_constraints&&!debug)thenprint_constraintcelse();beginmatchcwith|Instantiation_->Q.addcinst_worklist|Unification_->Q.addceq_worklistend;if(!debug)thensolve_constraints()else()(** Add a new constraint introduced through this module's interface (a
top-level constraint). *)andadd_constraint(c:su_constraint)=beginadd_constraint_int(c);if(!print_constraints&¬(!debug))thenprint_constraintcelse();if(!solve_online)thensolve_constraints()else()end(* Fetch constraints, preferring equalities. *)andfetch_constraint():su_constraintoption=if(Q.lengtheq_worklist>0)thenSome(Q.takeeq_worklist)elseif(Q.lengthinst_worklist>0)thenSome(Q.takeinst_worklist)elseNone(** Returns the target of a cached instantiation, if it exists. *)andtarget(t,i,p:tau*int*polarity):(polarity*tau)option=letcache=get_cachetinif(global_taut)thenSome(Non,t)elsetrySome(H.findcachei)with|Not_found->None(** Caches a new instantiation, or applies well-formedness. *)andstore(t,(i,p),t':tau*(int*polarity)*tau):bool=letcache=get_cachetinmatchtarget(t,i,p)with|Some(p'',t'')->if(U.equal(t',t'')&&(lub(p,p'')=p''))thenfalseelsebeginadd_constraint_int(Unification(t',t''));H.replacecachei(lub(p,p''),t'');(* add a new forced instantiation as well *)if(lub(p,p'')=p'')then()elsebeginunstore(t,i);add_constraint_int(Instantiation(t,(i,lub(p,p'')),t''))end;falseend|None->beginH.addcachei(p,t');trueend(** Remove a cached instantiation. Used when type structure changes *)andunstore(t,i:tau*int)=letcache=get_cachetinH.removecachei(** The main solver loop. *)andsolve_constraints():unit=matchfetch_constraint()with|Somec->begin(matchcwith|Instantiation(t,(i,p),t')->instantiate_int(t,(i,p),t')|Unification(t,t')->unify_int(t,t'));solve_constraints()end|None->()(***********************************************************************)(* *)(* Interface Functions *)(* *)(***********************************************************************)(** Return the contents of the lvalue. *)letrvalue(lv:lvalue):tau=lv.contents(** Dereference the rvalue. If it does not have enough structure to support
the operation, then the correct structure is added via new unification
constraints. *)letrecderef(t:tau):lvalue=matchU.dereftwith|Pairp->(matchU.deref(p.ptr)with|Var_->begin(* let points_to = make_pair(fresh_var(),fresh_var()) in *)letpoints_to=fresh_var()inletl=fresh_label()inletr=make_ref(l,points_to)inadd_constraint(Unification(p.ptr,r));make_lval(l,points_to)end|Refr->make_lval(r.rl,r.points_to)|_->raise(Inconsistent("deref")))|Varv->beginadd_constraint(Unification(t,make_pair(fresh_var(),fresh_var())));dereftend|_->raise(Inconsistent("deref -- no top level pair"))(** Form the union of [t] and [t']. *)letjoin(t:tau)(t':tau):tau=lett''=fresh_var()inadd_constraint(Unification(t,t''));add_constraint(Unification(t',t''));t''(** Form the union of a list [tl], expected to be the initializers of some
structure or array type. *)letjoin_inits(tl:taulist):tau=lett'=fresh_var()inbeginList.iter(functiont''->add_constraint(Unification(t',t'')))tl;t'end(** Take the address of an lvalue. Does not add constraints. *)letaddress(lv:lvalue):tau=make_pair(make_ref(lv.l,lv.contents),fresh_var())(** Instantiate a type with index i. By default, uses positive polarity.
Adds an instantiation constraint. *)letinstantiate(lv:lvalue)(i:int):lvalue=if(!analyze_mono)thenlvelsebeginletl'=fresh_label()inlett'=fresh_var_i()ininstantiate_label(lv.l,(i,Pos),l');add_constraint(Instantiation(lv.contents,(i,Pos),t'));make_lval(l',t')(* check -- fresh label ?? *)end(** Constraint generated from assigning [t] to [lv]. *)letassign(lv:lvalue)(t:tau):unit=add_constraint(Unification(lv.contents,t))(** Project out the first (ref) component or a pair. If the argument [t] has
no discovered structure, raise No_contents. *)letproj_ref(t:tau):tau=matchU.dereftwith|Pairp->p.ptr|Varv->raiseNo_contents|_->raiseBad_proj(* Project out the second (fun) component of a pair. If the argument [t] has
no discovered structure, create it on the fly by adding constraints. *)letproj_fun(t:tau):tau=matchU.dereftwith|Pairp->p.lam|Varv->letp,f=fresh_var(),fresh_var()inadd_constraint(Unification(t,make_pair(p,f)));f|_->raiseBad_projletget_args(t:tau):taulistref=matchU.dereftwith|Funf->f.args|_->raise(Inconsistent("get_args"))(** Function type [t] is applied to the arguments [actuals]. Unifies the
actuals with the formals of [t]. If no functions have been discovered for
[t] yet, create a fresh one and unify it with t. The result is the return
value of the function. *)letapply(t:tau)(al:taulist):tau=letf=proj_fun(t)inletactuals=refalinletformals,ret=matchU.dereffwith|Funfi->(fi.args),fi.ret|Varv->letnew_l,new_ret,new_args=fresh_label(),fresh_var(),Util.list_map(function_->fresh_var())(!actuals)inletnew_fun=make_fun(new_l,new_args,new_ret)inadd_constraint(Unification(new_fun,f));(get_argsnew_fun,new_ret)|Ref_->raise(Inconsistent("apply_ref"))|Pair_->raise(Inconsistent("apply_pair"))inpad_args(formals,actuals);List.iter2(funactual->funformal->add_constraint(Unification(actual,formal)))!actuals!formals;ret(** Create a new function type with name [name], list of formal arguments
[formals], and return value [ret]. Adds no constraints. *)letmake_function(name:string)(formals:lvaluelist)(ret:tau):tau=letf=make_fun(make_label(name),Util.list_map(funx->rvaluex)formals,ret)inmake_pair(fresh_var(),f)(** Create an lvalue. If [is_global] is true, the lvalue will be treated
monomorphically. *)letmake_lvalue(is_global:bool)(name:string):lvalue=if(!debug&&is_global)thenPrintf.printf"Making global lvalue : %s\n"nameelse();make_lval(make_label(name),make_varis_globalname)(** Create a fresh non-global named variable. *)letmake_fresh(name:string):tau=make_varfalse(name)(** The default type for constants. *)letbottom():tau=make_varfalse("bottom")(** Unify the result of a function with its return value. *)letreturn(t:tau)(t':tau)=add_constraint(Unification(t,t'))(***********************************************************************)(* *)(* Query/Extract Solutions *)(* *)(***********************************************************************)(** Unify the data stored in two label bounds. *)letcombine_lbounds(s,s':labelboundset*labelboundset)=B.unionss'(** Truncates a list of urefs [l] to those elements up to and including the
first occurence of the specified element [elt]. *)lettruncatelelt=letkeep=reftrueinList.filter(funx->if(not(!keep))thenfalseelsebeginif(U.equal(x,elt))thenkeep:=falseelse();trueend)lletdebug_cycle_boundsis_posc=letrecdebug_cycle_bounds'=function|h::[]->Printf.printf"%s --> %s\n"(string_of_boundsis_posh)(string_of_label2h)|h::t->beginPrintf.printf"%s --> %s\n"(string_of_boundsis_posh)(string_of_label2h);debug_cycle_bounds'tend|[]->()indebug_cycle_bounds'c(** For debugging, print a cycle of instantiations *)letdebug_cycle(is_pos,c,l,p)=letkind=ifis_posthen"P"else"N"inletrecstring_of_cycle=function|h::[]->string_of_label2h|[]->""|h::t->Printf.sprintf"%s,%s"(string_of_label2h)(string_of_cyclet)inPrintf.printf"Collapsing %s cycle around %s:\n"kind(string_of_label2l);Printf.printf"Elements are: %s\n"(string_of_cyclec);Printf.printf"Per-element bounds:\n";debug_cycle_boundsis_posc;Printf.printf"Full path is: %s"(string_of_cyclep);print_newline()(** Compute pos or neg flow, depending on [is_pos]. Searches for cycles in the
instantiations (can these even occur?) and unifies either the positive or
negative edge sets for the labels on the cycle. Note that this does not
ever unify the labels themselves. The return is the new bounds of the
argument label *)letrecflow(is_pos:bool)(path:labellist)(l:label):labelboundset=letcollapse_cycle()=letcycle=truncatepathlindebug_cycle(is_pos,cycle,l,path);List.iter(funx->U.unifycombine_lbounds((get_boundsis_posx),get_boundsis_posl))cycleinif(on_pathl)thenbegincollapse_cycle();(* set_on_path l false; *)B.emptyendelseif((is_pos&&(U.derefl).p_cached)||((notis_pos)&&(U.derefl).n_cached))thenbeginU.deref(get_boundsis_posl)endelsebeginletnewbounds=refB.emptyinletbase=get_boundsis_poslinset_on_pathltrue;if(is_pos)then(U.derefl).p_cached<-trueelse(U.derefl).n_cached<-true;B.iter(funx->if(U.equal(x.info,l))then()else(newbounds:=(B.union(!newbounds)(flowis_pos(l::path)x.info))))(U.derefbase);set_on_pathlfalse;U.update(base,(B.union(U.derefbase)!newbounds));U.derefbaseend(** Compute and cache any positive flow. *)letpos_flowl:constantset=letresult=refC.emptyinbeginignore(flowtrue[]l);B.iter(funx->result:=C.union(!result)(U.deref(x.info)).aliases)(U.deref(get_boundstruel));!resultend(** Compute and cache any negative flow. *)letneg_flowl:constantset=letresult=refC.emptyinbeginignore(flowfalse[]l);B.iter(funx->result:=C.union(!result)(U.deref(x.info)).aliases)(U.deref(get_boundsfalsel));!resultend(** Compute and cache any pos-neg flow. Assumes that both pos_flow and
neg_flow have been computed for the label [l]. *)letpos_neg_flow(l:label):constantset=letresult=refC.emptyinbeginB.iter(funx->result:=C.union(!result)(pos_flowx.info))(U.deref(get_boundsfalsel));!resultend(** Compute a points-to set by computing positive, then negative, then
positive-negative flow for a label. *)letpoints_to_int(lv:lvalue):constantset=letvisited_caches:cachelistref=ref[]inletrecpoints_to_tau(t:tau):constantset=trybeginmatchU.deref(proj_reft)with|Varv->C.empty|Refr->beginletpos=pos_flowr.rlinletneg=neg_flowr.rlinletinterproc=C.union(pos_neg_flowr.rl)(C.unionposneg)inC.union((U.deref(r.rl)).aliases)interprocend|_->raise(Inconsistent("points_to"))endwith|No_contents->beginmatch(U.dereft)with|Varv->rebuild_flowv.v_cache|_->raise(Inconsistent("points_to"))endandrebuild_flow(c:cache):constantset=if(List.memc(!visited_caches))(* cyclic instantiations *)thenbegin(* visited_caches := List.tl (!visited_caches); *)(* check *)C.emptyendelsebeginvisited_caches:=c::(!visited_caches);letresult=ref(C.empty)inH.iter(fun_->fun(p,t)->matchpwith|Pos->()|_->result:=C.union(!result)(points_to_taut))c;visited_caches:=List.tl(!visited_caches);!resultendinif(!no_flow)then(U.dereflv.l).aliaseselsepoints_to_tau(lv.contents)letpoints_to(lv:lvalue):stringlist=Util.list_mapsnd(C.elements(points_to_intlv))letalias_query(a_progress:bool)(lv:lvaluelist):int*int=(0,0)(* todo *)(*
let a_count = ref 0 in
let ptsets = Util.list_map points_to_int lv in
let total_sets = List.length ptsets in
let counted_sets = ref 0 in
let record_alias s s' =
if (C.is_empty (C.inter s s'))
then ()
else (incr a_count)
in
let rec check_alias = function
| h :: t ->
begin
List.iter (record_alias h) ptsets;
check_alias t
end
| [] -> ()
in
check_alias ptsets;
!a_count
*)