123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885(* Yoann Padioleau
*
* Copyright (C) 2012 Facebook
*
* This library is free software; you can redistribute it and/or
* modify it under the terms of the GNU Lesser General Public License
* version 2.1 as published by the Free Software Foundation, with the
* special exception on linking described in file license.txt.
*
* This library is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the file
* license.txt for more details.
*)openCommonmoduleE=Entity_codemoduleG=Graph_codeopenAst_javamoduleAst=Ast_javamodulePI=Parse_info(*****************************************************************************)(* Prelude *)(*****************************************************************************)(*
* Graph of dependencies for Java. See graph_code.ml and main_codegraph.ml
* for more information.
*
* choices:
* - package-based or dir-based schema? Seems simpler to use packages.
* - merge overloaded methods? yes, alternative is to mangle the
* name of the method with the type (a la C++ linker)
*
* schema:
* Package -> SubPackage -> Class (TODO | Interface )
* -> Method
* -> Field
* -> Constant (static final)
* -> Constant (enum, inlined in parent)
* Class -> SubClass -> ...
* -> EnumSubClass (nothing)
* (when have no package)
* Dir -> Subdir -> File -> Class
*
* PB -> Not_Found -> Package2 -> SubPackage2 -> ...
*
* note: adjust graph to remove intermediate singleton? com.xxx? Hmm better
* to do that lazily in codegraph itself.
*
* note: doing codegraph for Java helps evaluate the number of lookup failures
* in projects, and which code one needs to include to fully analyze the code.
* If I go in the abstract interpreter path that julien took where he analyzed
* code but had so many Not_found, Todo, exn, then I'll have no confidence
* at all. So:
*
* - DONE lookup package correctly
* - SEMI lookup classes correctly
* - lookup field/methods correctly
*
* It also helps to find bug in the parser and better understand
* Java and the AST :) e.g. Name -> Dot ambiguities.
* It also helps to see which code is needed to fully analyze our code.
*
*)(*****************************************************************************)(* Types *)(*****************************************************************************)typeenv={g:Graph_code.graph;phase:phase;current:Graph_code.node;current_qualifier:Ast_java.qualified_ident;(* import x.y.* => [["x";"y"]; ...] *)imported_namespace:(stringlist)list;(* import x.y.z => [("z", (false, ["x";"y";"z"])); ...] *)imported_qualified:(string*(bool*Ast_java.qualified_ident))list;(* This field is to avoid looking up parameters or locals in the graph.
* We could also store them in the code graph so that the lookup
* would work, but really fine-grained intra-method dependencies
* are not that useful.
*
* The boolean final is because such locals/parameters should be
* passed to anonymouse classes.
*)params_or_locals:(string*bool(* is_final *))list;(* To avoid looking up type parameters in the graph. *)type_parameters:stringlist;}(* We need 3 phases, one to get all the definitions, one to
* get the inheritance information, and one to get all the Uses.
* The inheritance is a kind of use, but certain uses like using
* a field needs the full inheritance tree to already be computed
* as we may need to lookup entities up in the parents.
*)andphase=Defs|Inheritance|Uses(*****************************************************************************)(* Helpers *)(*****************************************************************************)letparse~show_parse_errorfile=tryParse_java.parse_programfilewith|Timeout->raiseTimeout|exn->ifshow_parse_errorthenpr2_once(spf"PARSE ERROR with %s, exn = %s"file(Common.exn_to_sexn));{package=None;imports=[];decls=[]}letstr_of_qualified_identxs=xs|>List.mapAst.unwrap|>Common.join"."letstr_of_namexs=xs|>List.map(fun(_tyarg_todo,ident)->Ast.unwrapident)|>Common.join"."(* helper to build entries in env.params_or_locals *)letp_or_lv=Ast.unwrapv.v_name,Ast.is_finalv.v_mods(* TODO *)letlong_ident_of_namexs=List.mapsndxs(* TODO *)letlong_ident_of_class_typexs=List.mapfstxsletnodeinfoident={G.pos=Parse_info.token_location_of_info(Ast.info_of_identident);props=[];typ=None;}letlooks_like_class_names=s=~"[A-Z]"letlooks_like_enum_constants=s=~"^[A-Z_0-9]+$"letrecclassname_and_info_of_typt=matchtwith|TBasicx->x|TArrayt->classname_and_info_of_typt|TClassxs->letx=Common2.list_lastxsinlet(ident,_args)=xinident(* quite similar to create_intermediate_directories_if_not_present *)letcreate_intermediate_packages_if_not_presentgrootxs=letdirs=Common2.initsxs|>List.mapstr_of_qualified_identinletdirs=matchdirswith|""::xs->xs|_->raiseImpossibleinletrecauxcurrentxs=matchxswith|[]->()|x::xs->letentity=x,E.PackageinifG.has_nodeentitygthenauxentityxselsebeging|>G.add_nodeentity;g|>G.add_edge(current,entity)G.Has;auxentityxsendinauxrootdirsletadd_use_edgeenv(name,kind)=letsrc=env.currentinletdst=(name,kind)in(match()with|_whennot(G.has_nodesrcenv.g)->pr2(spf"LOOKUP SRC FAIL %s --> %s, src does not exist???"(G.string_of_nodesrc)(G.string_of_nodedst));|_whenG.has_nodedstenv.g->G.add_edge(src,dst)G.Useenv.g|_->(matchkindwith|_->letkind_original=kindinletdst=(name,kind_original)inletparent_target=G.not_foundin(matchkind_originalwith|E.Package->letfake_package=(Common.split"\\."name)|>List.map(funs->s^"2")inletdst=(Common.join"."fake_package,kind_original)inifnot(G.has_nodedstenv.g)thenbegincreate_intermediate_packages_if_not_presentenv.gparent_target(fake_package|>List.map(funs->s,()));pr2(spf"PB: lookup fail on %s (in %s)"(G.string_of_nodedst)(G.string_of_nodesrc));end;env.g|>G.add_edge(src,dst)G.Use;()|_->pr2(spf"PB: lookup fail on %s (in %s)"(G.string_of_nodedst)(G.string_of_nodesrc));G.add_nodedstenv.g;env.g|>G.add_edge(parent_target,dst)G.Has;env.g|>G.add_edge(src,dst)G.Use;)))(*****************************************************************************)(* Class/Package Lookup *)(*****************************************************************************)let_hmemo=Hashtbl.create101letlookup_fully_qualified_memoizedenvx=Common.profile_code"Graph_java.lookup_qualified"(fun()->ifenv.phase=Uses||env.phase=InheritancethenCommon.memoized_hmemox(fun()->Package_java.lookup_fully_qualified2env.gx)elsePackage_java.lookup_fully_qualified2env.gx)(* Java allows to open namespaces by for instance importing packages
* in which case we unsugar by preprending the package name.
* Note that extending a class also imports its namespace (and
* of all its parents too), hence import_of_inherited_classes below.
*)letwith_full_qualifierenvxs=env.imported_namespace|>List.map(fun(qualified_ident)->letrev=List.revqualified_identinletprefix=(* todo: simplify now that have imported_qualified? *)matchrevwith|("*")::rest->List.revrest(* todo opti: if head match the head of xs, then can accelerate things? *)|_->List.rev(List.tlrev)inprefix@(xs|>List.mapAst.unwrap))(* Look for entity (package/class/method/field) in list of imported
* packages or in global scope. Return fully qualified entity.
*
* Note that the code graph store nodes in fully qualified form.
*)let(lookup2:env->Ast.qualified_ident->Graph_code.nodeoption)=funenvxs->letcandidates=with_full_qualifierenvxsin(* pr2_gen candidates; *)candidates|>Common.find_some_opt(funfull_qualifier->lookup_fully_qualified_memoizedenvfull_qualifier)letlookupab=Common.profile_code"Graph_java.lookup"(fun()->lookup2ab)(* pre: the Inheritance phase must have been done already
* otherwise parents_inheritance can be empty or incomplete.
*)letrecimport_of_inherited_classesenvn=(* A class should Use only entities its extends or implements.
* less: could filter out interface but needs them to store
* then as E.Class E.Interface
*)letparents_inheritance=G.succnG.Useenv.ginparents_inheritance|>Common.map_filter(fun(str,kind)->matchkindwith|E.Class->letxs=(Common.split"\\."str)@["*"]inletres=import_of_inherited_classesenv(str,kind)inSome(xs::res)|_->None)|>List.flatten(*****************************************************************************)(* Defs/Uses *)(*****************************************************************************)(* Note that there is no ~dupe argument. Java code uses packages and
* fully qualified entities so there should be no name conflicts.
*)letrecextract_defs_uses~phase~g~ast~readable~lookup_fails=ignore(lookup_fails);letenv={g;phase;current=(matchast.packagewith|Somelong_ident->(str_of_qualified_identlong_ident,E.Package)|None->(readable,E.File));current_qualifier=(matchast.packagewith|None->[]|Somelong_ident->long_ident);params_or_locals=[];type_parameters=[];imported_namespace=(matchast.packagewith(* we automatically import the current.package.* *)|Somelong_ident->[List.mapAst.unwraplong_ident@["*"]]|None->[])@((ast.imports|>List.map(fun(_is_static,qualified_ident)->List.mapAst.unwrapqualified_ident))@[(* we automatically import java.lang.* *)["java";"lang";"*"];(* we automatically import top packages *)["*"]]);imported_qualified=ast.imports|>Common.map_filter(fun(is_static,xs)->matchList.revxswith|[]->raiseImpossible|["*",_]->None|(s,_)::_rest->Some(s,(is_static,xs)));}inifphase=Defsthenbeginmatchast.packagewith(* have None usually for scripts, tests, or entry points *)|None->letdir=Common2.dirnamereadableinG.create_intermediate_directories_if_not_presentgdir;g|>G.add_node(readable,E.File);g|>G.add_edge((dir,E.Dir),(readable,E.File))G.Has;|Somelong_ident->create_intermediate_packages_if_not_presentgG.rootlong_ident;end;(* double check if we can find some of the imports
* (especially useful when have a better java_stdlib/ to report
* third-party packages not-yet handled).
*)ifphase=Inheritancethenbeginast.imports|>List.iter(fun(is_static,qualified_ident)->letqualified_ident_bis=matchList.revqualified_identwith|("*",_)::rest->List.revrest(* less: just lookup the class for now *)|_x::xswhenis_static->List.revxs|_->qualified_identinletentity=List.mapAst.unwrapqualified_ident_bisin(matchlookup_fully_qualified_memoizedenventitywith|Some_->(* no need add_use_edge here, it will be done later when
* one use the entity
* less: could be used to detect useless import
*)()|None->pr2_once(spf"PB: wrong import: %s"(str_of_qualified_identqualified_ident_bis))));end;(* imports is not the only way to use external packages, one can
* also just qualify the classname or static method so we need
* to visit the AST and lookup classnames (possibly using information
* from the import to know where to look for first).
*)declsenvast.decls(* ---------------------------------------------------------------------- *)(* Declarations (classes, fields, etc) *)(* ---------------------------------------------------------------------- *)anddeclenv=function|Classdef,_->class_declenvdef|Methoddef,_->method_declenvdef|Fielddef,_->field_declenvdef|Enumdef,_->enum_declenvdef|Init(_is_static,st),n->letname=spf"__init__%d"ninletfull_ident=env.current_qualifier@[name,fakeInfoname]inletfull_str=str_of_qualified_identfull_identinletnode=(full_str,E.TopStmts)inifenv.phase=Defsthenbeginenv.g|>G.add_nodenode;env.g|>G.add_edge(env.current,node)G.Has;end;letenv={envwithcurrent=node;current_qualifier=full_ident;}instmtenvstanddeclsenvxs=List.iter(declenv)(Common.index_list_1xs)andclass_declenvdef=letfull_ident=env.current_qualifier@[def.cl_name]inletfull_str=str_of_qualified_identfull_identinletnode=(full_str,E.Class)inifenv.phase=Defsthenbegin(* less: def.c_type? *)env.g|>G.add_nodenode;env.g|>G.add_nodeinfonode(nodeinfodef.cl_name);env.g|>G.add_edge(env.current,node)G.Has;end;letenv={envwithcurrent=node;current_qualifier=full_ident;(* with anon classes we need to lookup enclosing final parameters/locals *)params_or_locals=env.params_or_locals|>List.filter(fun(_x,b)->b);type_parameters=def.cl_tparams|>List.map(function|TParam((str,_tok),_constraints)->str);}inletparents=Common2.option_to_listdef.cl_extends@(def.cl_impls)inList.iter(typenv)parents;letimports=ifenv.phase=Defsthen[]else(* Java allows programmer to use fields without qualifying them
* (without a class.xxx, or this.xxx) so we need to unsugar this
* by prepending the full current classname. We can just
* generate a fake import package.classname.*. This will also
* allow nested classes to access siblings.
*)(List.mapAst.unwrapfull_ident@["*"])::import_of_inherited_classesenv(full_str,E.Class)indecls{envwithimported_namespace=imports@env.imported_namespace}def.cl_body(* Java allow some forms of overloading, so the same method name can be
* used multiple times.
*)andmethod_declenvdef=letfull_ident=env.current_qualifier@[def.m_var.v_name]inletfull_str=str_of_qualified_identfull_identinletnode=(full_str,E.Method)inifenv.phase=Defsthenbegin(* less: static? *)(* less: for now we just collapse all methods with same name together *)ifG.has_node(full_str,E.Method)env.gthen()elsebeginenv.g|>G.add_nodenode;env.g|>G.add_nodeinfonode(nodeinfodef.m_var.v_name);env.g|>G.add_edge(env.current,node)G.Has;endend;letenv={envwithcurrent=node;(* No change to the qualifier? methods are not a namespace?
* Hmm but can have nested classes inside a methods that
* share the same name so yes need full_ident as a qualifier.
*)current_qualifier=full_ident;params_or_locals=(def.m_formals|>List.mapp_or_l)@(* with methods of anon classes we need to lookup enclosing
* final parameters/locals
*)(env.params_or_locals|>List.filter(fun(_x,b)->b));(* TODO use m_tparams *)type_parameters=[];}invarenvdef.m_var;List.iter(varenv)def.m_formals;(* todo: m_throws *)stmtenvdef.m_bodyandfield_declenvdef=letfull_ident=env.current_qualifier@[def.f_var.v_name]inletfull_str=str_of_qualified_identfull_identinletkind=ifAst.is_final_staticdef.f_var.v_modsthenE.ConstantelseE.Fieldinletnode=(full_str,kind)inifenv.phase=Defsthenbegin(* less: static? *)env.g|>G.add_nodenode;env.g|>G.add_nodeinfonode(nodeinfodef.f_var.v_name);env.g|>G.add_edge(env.current,node)G.Has;end;letenv={envwithcurrent=node;current_qualifier=env.current_qualifier}infieldenvdefandenum_declenvdef=letfull_ident=env.current_qualifier@[def.en_name]inletfull_str=str_of_qualified_identfull_identin(* less: make it a class? or a Type? *)letnode=(full_str,E.Class)inifenv.phase=Defsthenbeginenv.g|>G.add_nodenode;env.g|>G.add_nodeinfonode(nodeinfodef.en_name);env.g|>G.add_edge(env.current,node)G.Has;end;letenv={envwithcurrent=node;current_qualifier=full_ident;params_or_locals=[];(* TODO *)type_parameters=[];}inletparents=(def.en_impls)inList.iter(typenv)parents;let(csts,xs)=def.en_bodyindeclsenvxs;csts|>List.iter(funenum_constant->letident=matchenum_constantwith|EnumSimpleid|EnumConstructor(id,_)|EnumWithMethods(id,_)->idinletfull_ident=env.current_qualifier@[ident]inletfull_str=str_of_qualified_identfull_identinletnode=(full_str,E.Constant)inifenv.phase=Defsthenbeginenv.g|>G.add_nodenode;env.g|>G.add_nodeinfonode(nodeinfoident);env.g|>G.add_edge(env.current,node)G.Has;end;letenv={envwithcurrent=node;current_qualifier=full_ident;}in(matchenum_constantwith|EnumSimple_ident->()|EnumConstructor(_ident,args)->exprsenvargs|EnumWithMethods(_ident,xs)->declsenv(xs|>List.map(funx->Methodx))))(* ---------------------------------------------------------------------- *)(* Stmt *)(* ---------------------------------------------------------------------- *)(* mostly boilerplate, control constructs don't introduce entities *)andstmtenv=function|Empty->()|Blockxs->stmtsenvxs|Expre->exprenve|If(e,st1,st2)->exprenve;stmtenvst1;stmtenvst2;|Switch(e,xs)->exprenve;xs|>List.iter(fun(cs,sts)->casesenvcs;stmtsenvsts)|While(e,st)->exprenve;stmtenvst;|Do(st,e)->exprenve;stmtenvst;|For(x,st)->letenv=matchxwith|Foreach(v,e)->varenvv;exprenve;{envwithparams_or_locals=p_or_lv::env.params_or_locals;}|ForClassic(init,es1,es2)->(matchinitwith|ForInitExprses0->exprsenv(es0@es1@es2);env|ForInitVarsxs->List.iter(fieldenv)xs;letenv={envwithparams_or_locals=(xs|>List.map(funfld->p_or_lfld.f_var))@env.params_or_locals;}inexprsenv(es1@es2);env)instmtenvst;(* could have an entity and dependency ... but it's intra procedural
* so not that useful
*)|Label(_id,st)->stmtenvst|Break_idopt|Continue_idopt->()|Returneopt->exprsenv(Common2.option_to_listeopt)|Sync(e,st)->exprenve;stmtenvst;|Try(st,xs,stopt)->stmtenvst;catchesenvxs;stmtsenv(Common2.option_to_liststopt);|Throwe->exprenve|Assert(e,eopt)->exprsenv(e::Common2.option_to_listeopt)(* The modification of env.params_locals is done in decls() *)|LocalVarf->fieldenvf|LocalClassdef->class_declenvdefandstmtsenvxs=letrecauxenv=function|[]->()|x::xs->stmtenvx;letenv=matchxwith|LocalVarfld->{envwithparams_or_locals=p_or_lfld.f_var::env.params_or_locals}(* also add LocalClass case? no, 'lookup env ...' handles that *)|_->envinauxenvxsinauxenvxsandcasesenvxs=List.iter(caseenv)xsandcaseenv=function|Casee->exprenve|Default->()andcatchesenvxs=List.iter(catchenv)xsandcatchenv(v,st)=varenvv;letenv={envwithparams_or_locals=p_or_lv::env.params_or_locals}instmtenvst(* ---------------------------------------------------------------------- *)(* Expr *)(* ---------------------------------------------------------------------- *)andexprenv=function(* main dependency source! *)|Namen->ifenv.phase=Usesthenbeginletstr=str_of_namenin(matchstr,nwith(* TODO: look at the type and continue lookup *)|_,(_,(s,_))::_restwhenList.mem_assocsenv.params_or_locals->()(* TODO *)|"super",_|"this",_->()|_->(matchlookupenv(long_ident_of_namen)with|Somen2->add_use_edgeenvn2|None->(matchnwith|[]->pr2"Name is empty??";pr2_gen(env.current,n);raiseImpossible|(_,(s,_))::_whenList.mem_assocsenv.imported_qualified->let(_is_static,full_ident)=List.assocsenv.imported_qualifiedinletstr=str_of_qualified_identfull_identinadd_use_edgeenv(str,E.Package)|[_x]whenlooks_like_enum_constantstr->pr2("PB: "^Common.dumpn);|[_x]whenlooks_like_class_namestr->add_use_edgeenv(str,E.Package)|[_x]->pr2("PB: "^Common.dumpn);(* env.imported_namespace +> List.iter pr2_gen; *)|_x::_y::_xs->(* unknown package probably *)add_use_edgeenv(str,E.Package))))end|NameOrClassType_->()|Literal_->()|ClassLiteralt->typenvt|NewClass(t,args,decls_opt)->typenvt;exprsenvargs;(matchdecls_optwith|None->()|Somexs->(* less: quite similar to class_decl, factorize code? *)letclassname,info=classname_and_info_of_typtinletcharpos=PI.pos_of_infoinfoinletanon_class=spf"__anon__%s__%d"classnamecharposinletcdecl={cl_name=(anon_class,info);cl_extends=Somet;cl_impls=[];cl_kind=ClassRegular;cl_body=xs;(* ?? *)cl_tparams=[];cl_mods=[];}inclass_declenvcdecl)|NewQualifiedClass(_e,id,args,decls_opt)->(*
pr2 "NewQualifiedClass";
pr2_gen (NewQualifiedClass (e, id, args, decls_opt));
*)(* todo: need to resolve the type of 'e' *)exprenv(NewClass(TClass([id,[]]),args,decls_opt))|NewArray(t,args,_i,ini_opt)->typenvt;exprsenvargs;init_optenvini_opt|Call(e,es)->exprenve;exprsenves|Dot(e,_idTODO)->(* todo: match e, and try lookup method/field
* if e is a Name, lookup it, and if a class then
* lookup children. If local ... then need get its type
* lookup its node, and then lookup children.
*)exprenve;|ArrayAccess(e1,e2)->exprsenv[e1;e2]|Postfix(e,_)|Prefix(_,e)|Unary(_,e)->exprenve|Infix(e1,_op,e2)->exprsenv[e1;e2]|Conditional(e1,e2,e3)->exprsenv[e1;e2;e3]|AssignOp(e1,_op,e2)->exprsenv[e1;e2]|Assign(e1,e2)->exprsenv[e1;e2]|Cast(t,e)->typenvt;exprenve|InstanceOf(e,tref)->exprenve;typenv(tref);|Ellipses_->()andexprsenvxs=List.iter(exprenv)xsandinitenv=function|ExprInite->exprenve|ArrayInitxs->List.iter(initenv)xsandinit_optenvopt=matchoptwith|None->()|Someini->initenvini(* ---------------------------------------------------------------------- *)(* Types *)(* ---------------------------------------------------------------------- *)andtypenv=function|TBasic_->()|TArrayt->typenvt(* other big dependency source! *)|TClassreft->(* todo: let's forget generic arguments for now *)letxs=long_ident_of_class_typereftinletstr=str_of_qualified_identxsinifenv.phase=Uses||env.phase=Inheritancethenbegin(matchstr,reftwith(* TODO: look at the type and continue lookup *)|_,(((s,_),_))::_restwhenList.memsenv.type_parameters->()|_->(matchlookupenvxswith(* TODO: look in type_params_local ! *)|Somen2->(* pr2 ("FOUND: " ^ Common.dump n); *)add_use_edgeenvn2|None->(matchxswith|[]->raiseImpossible|((s,_))::_whenList.mem_assocsenv.imported_qualified->let(_is_static,full_ident)=List.assocsenv.imported_qualifiedinletstr=str_of_qualified_identfull_identinadd_use_edgeenv(str,E.Package)|[_x]->iflooks_like_class_namestrthenadd_use_edgeenv(str,E.Package)elsepr2("PB: "^Common.dumpreft);|_x::_y::_xs->(* unknown package probably *)add_use_edgeenv(str,E.Package))))end(* ---------------------------------------------------------------------- *)(* Misc *)(* ---------------------------------------------------------------------- *)andvarenvv=typenvv.v_type;()andfieldenvf=varenvf.f_var;init_optenvf.f_init;()(*****************************************************************************)(* Main entry point *)(*****************************************************************************)letbuild?(verbose=true)?(only_defs=false)rootfiles=letg=G.create()inG.create_initial_hierarchyg;letlookup_fails=Common2.hash_with_default(fun()->0)in(* step1: creating the nodes and 'Has' edges, the defs *)ifverbosethenpr2"\nstep1: extract defs";files|>Console.progress~show:verbose(funk->List.iter(funfile->k();letreadable=Common.readable~rootfileinletast=parse~show_parse_error:truefileinextract_defs_uses~phase:Defs~g~ast~readable~lookup_fails;));ifnotonly_defsthenbegin(* step2: creating the 'Use' edges just for inheritance *)ifverbosethenpr2"\nstep2: extract inheritance information";files|>Console.progress~show:verbose(funk->List.iter(funfile->k();letreadable=Common.readable~rootfileinletast=parse~show_parse_error:falsefileinextract_defs_uses~phase:Inheritance~g~ast~readable~lookup_fails;));(* step3: creating the 'Use' edges that can rely on recursive inheritance *)ifverbosethenpr2"\nstep3: extract uses";files|>Console.progress~show:verbose(funk->List.iter(funfile->k();letreadable=Common.readable~rootfileinletast=parse~show_parse_error:falsefileinextract_defs_uses~phase:Uses~g~ast~readable~lookup_fails;));end;g