123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182(**************************************************************************)(* *)(* This file is part of Frama-C. *)(* *)(* Copyright (C) 2007-2025 *)(* CEA (Commissariat à l'énergie atomique et aux énergies *)(* alternatives) *)(* *)(* you can redistribute it and/or modify it under the terms of the GNU *)(* Lesser General Public License as published by the Free Software *)(* Foundation, version 2.1. *)(* *)(* It is distributed in the hope that it will be useful, *)(* but WITHOUT ANY WARRANTY; without even the implied warranty of *)(* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the *)(* GNU Lesser General Public License for more details. *)(* *)(* See the GNU Lesser General Public License version 2.1 *)(* for more details (enclosed in the file licenses/LGPLv2.1). *)(* *)(**************************************************************************)openDatamoduleMd=MarkdownmoduleJs=Yojson.Basic.UtilmodulePkg=PackageopenCil_typesletpackage=Pkg.package~title:"Ast Services"~name:"ast"~readme:"ast.md"()(* -------------------------------------------------------------------------- *)(* --- Compute Ast --- *)(* -------------------------------------------------------------------------- *)let()=Request.register~package~kind:`EXEC~name:"compute"~descr:(Md.plain"Ensures that AST is computed")~input:(moduleJunit)~output:(moduleJunit)Ast.computeletast_changed_signal=Request.signal~package~name:"changed"~descr:(Md.plain"Emitted when the AST has been changed")letast_changed()=Request.emitast_changed_signalletast_update_hookf=beginAst.add_hook_on_updatef;Ast.apply_after_computed(fun_->f());endlet()=ast_update_hookast_changedlet()=Annotations.add_hook_on_changeast_changed(* -------------------------------------------------------------------------- *)(* --- File Positions --- *)(* -------------------------------------------------------------------------- *)modulePosition=structtypet=Filepath.positionletjtype=Data.declare~package~name:"source"~descr:(Md.plain"Source file positions.")(Jrecord["dir",Jstring;"base",Jstring;"file",Jstring;"line",Jnumber;])letto_jsonp=letpath=Filepath.(to_stringp.pos_path)inletfile=ifServer_parameters.has_relative_filepath()thenpathelse(p.Filepath.pos_path:>string)in`Assoc["dir",`String(Filename.dirnamepath);"base",`String(Filename.basenamepath);"file",`Stringfile;"line",`Intp.Filepath.pos_lnum;]letof_jsonjs=letfail()=failure_from_type_error"Invalid source format"jsinmatchjswith|`Assocassoc->beginmatchList.assoc"file"assoc,List.assoc"line"assocwith|`Stringpath,`Intline->Log.source~file:(Filepath.of_stringpath)~line|_,_->fail()|exceptionNot_found->fail()end|_->fail()end(* -------------------------------------------------------------------------- *)(* --- Generic Markers --- *)(* -------------------------------------------------------------------------- *)moduletypeTagInfo=sigtypetvalname:stringvaldescr:stringvalcreate:t->stringmoduleH:Hashtbl.Swithtypekey=tendmoduletypeTag=sigincludeData.Svalindex:t->stringvalfind:string->tendmoduleMakeTag(T:TagInfo):sigincludeTagwithtypet=T.tvaliter:(t*string->unit)->unitvalhook:(t*string->unit)->unitend=structtypet=T.ttypeindex={tags:stringT.H.t;items:(string,T.t)Hashtbl.t;}letindex()={tags=T.H.create0;items=Hashtbl.create0;}letmodule_name=String.capitalize_asciiT.namemoduleTYPE:Datatype.Swithtypet=index=Datatype.Make(structtypet=indexincludeDatatype.Undefinedletreprs=[index()]letname=Printf.sprintf"Server.Kernel_ast.%s.TYPE"module_nameletmem_project=Datatype.never_any_projectend)moduleSTATE=State_builder.Ref(TYPE)(structletname=Printf.sprintf"Server.Kernel_ast.%s.STATE"module_nameletdependencies=[]letdefault=indexend)letiterf=T.H.iter(funkeystr->f(key,str))(STATE.get()).tagslethooks=ref[]lethookf=hooks:=!hooks@[f]letindexitem=let{tags;items}=STATE.get()intryT.H.findtagsitemwithNot_found->lettag=T.createiteminT.H.addtagsitemtag;Hashtbl.additemstagitem;List.iter(funfn->fn(item,tag))!hooks;tagletfindtag=Hashtbl.find(STATE.get()).itemstagletjtype=Data.declare~package~name:T.name~descr:(Md.plainT.descr)(Pkg.JkeyT.name)letto_jsonitem=`String(indexitem)letof_jsonjs=tryfind(Js.to_stringjs)withNot_found->Data.failure"invalid %s (%a)"T.nameJson.pp_dumpjsendmoduleDecl=MakeTag(structopenPrinter_tagtypet=declarationletname="decl"letdescr="AST Declarations markers"moduleH=Declaration.Hashtblletkid=ref0letcreate=function|SEnum_->Printf.sprintf"#E%d"(incrkid;!kid)|SComp_->Printf.sprintf"#C%d"(incrkid;!kid)|SType_->Printf.sprintf"#T%d"(incrkid;!kid)|SGlobalvi->Printf.sprintf"#G%d"vi.vid|SFunctionkf->Printf.sprintf"#F%d"@@Kernel_function.get_idkf|SGAnnot_->Printf.sprintf"#A%d"(incrkid;!kid)end)moduleMarker=MakeTag(structopenPrinter_tagtypet=localizableletname="marker"letdescr="Localizable AST markers"moduleH=Localizable.Hashtblletkid=ref0letcreate=function|PStmt(_,s)->Printf.sprintf"#s%d"s.sid|PStmtStart(_,s)->Printf.sprintf"#k%d"s.sid|PVDecl(_,_,v)->Printf.sprintf"#v%d"v.vid|PLval_->Printf.sprintf"#l%d"(incrkid;!kid)|PExp(_,_,e)->Printf.sprintf"#e%d"e.eid|PTermLval_->Printf.sprintf"#t%d"(incrkid;!kid)|PGlobal_->Printf.sprintf"#g%d"(incrkid;!kid)|PIP_->Printf.sprintf"#p%d"(incrkid;!kid)|PType_->Printf.sprintf"#y%d"(incrkid;!kid)end)modulePrinterTag=Printer_tag.Make(structlettag=Marker.indexend)(* -------------------------------------------------------------------------- *)(* --- Ast Data --- *)(* -------------------------------------------------------------------------- *)moduleLval=structopenPrinter_tagtypet=kinstr*lvalletjtype=Marker.jtypeletto_json(kinstr,lval)=letkf=matchkinstrwith|Kglobal->None|Kstmtstmt->Some(Kernel_function.find_englobing_kfstmt)inMarker.to_json(PLval(kf,kinstr,lval))letfind=function|PLval(_,kinstr,lval)->kinstr,lval|PVDecl(_,kinstr,vi)->kinstr,Cil.varvi|PGlobal(GVar(vi,_,_)|GVarDecl(vi,_))->Kglobal,Cil.varvi|_->raiseNot_foundletmemtag=trylet_=findtagintruewithNot_found->falseletof_jsonjs=tryfind(Marker.of_jsonjs)withNot_found->Data.failure"not a lval marker"endmoduleStmt=structtypet=stmtletjtype=Marker.jtypeletto_jsonst=letkf=Kernel_function.find_englobing_kfstinMarker.to_json(PStmtStart(kf,st))letof_jsonjs=letopenPrinter_taginmatchMarker.of_jsonjswith|PStmt(_,st)|PStmtStart(_,st)->st|_->Data.failure"not a stmt marker"endmoduleKinstr=structtypet=kinstrletjtype=Pkg.JoptionMarker.jtypeletto_json=function|Kglobal->`Null|Kstmtst->Stmt.to_jsonstletof_json=function|`Null->Kglobal|js->Kstmt(Stmt.of_jsonjs)end(* -------------------------------------------------------------------------- *)(* --- Declaration Attributes --- *)(* -------------------------------------------------------------------------- *)moduleDeclKind=structopenPrinter_tagtypet=declarationletjtype=Data.declare~package~name:"declKind"~descr:(Md.plain"Declaration kind")(Junion[(* C *)Jkey"ENUM";Jkey"UNION";Jkey"STRUCT";Jkey"TYPEDEF";Jkey"GLOBAL";Jkey"FUNCTION";(* ACSL *)Jkey"LFUNPRED";Jkey"INVARIANT";Jkey"AXIOMATIC";Jkey"MODULE";Jkey"LEMMA";Jkey"EXTENSION";Jkey"VOLATILE";Jkey"LTYPE";Jkey"MODEL";])letglobal_annotation_kind=function|Dfun_or_pred_->"LFUNPRED"|Dinvariant_->"INVARIANT"|Dtype_annot_->"INVARIANT"|Daxiomatic_->"AXIOMATIC"|Dmodule_->"MODULE"|Dlemma_->"LEMMA"|Dextended_->"EXTENSION"|Dvolatile_->"VOLATILE"|Dtype_->"LTYPE"|Dmodel_annot_->"MODEL"letto_json=function|SEnum_->`String"ENUM"|SComp{cstruct=true}->`String"STRUCT"|SComp{cstruct=false}->`String"UNION"|SType_->`String"TYPEDEF"|SGlobal_->`String"GLOBAL"|SFunction_->`String"FUNCTION"|SGAnnota->`String(global_annotation_kinda)endmoduleGAnnotRoots=structincludeState_builder.Hashtbl(Cil_datatype.Global_annotation.Hashtbl)(Datatype.Unit)(structletname="Server.Kernel_ast.GAnnotsRoots"letsize=43letdependencies=[Ast.self]end)letis_rootga=memgaendmoduleDeclAttributes=structopenPrinter_tagletmodel=States.model()(* We must iterate over all known declaration in the Ast, contrarily to
markers, for which we ony need attributes of already generated markers. *)letiter_declarationf=ifAst.is_computed()thenletmarked=Declaration.Hashtbl.create0inCil.iterGlobals(Ast.get())(fung->beginmatchgwith|GAnnot(ga,_)->GAnnotRoots.addga()|_->()end;matchdeclaration_of_globalgwith|None->()|Somed->ifnot@@Declaration.Hashtbl.memmarkeddthenbeginDeclaration.Hashtbl.addmarkedd();f(d,Decl.indexd)end)let()=States.column~name:"kind"~descr:(Md.plain"Declaration kind")~data:(moduleDeclKind)~get:fstmodellet()=States.column~name:"self"~descr:(Md.plain"Declaration's marker")~data:(moduleMarker)~get:(fun(decl,_)->localizable_of_declarationdecl)modellet()=States.column~name:"name"~descr:(Md.plain"Declaration identifier")~data:(moduleJstring)~get:(fun(decl,_)->name_of_declarationdecl)modellet()=States.column~name:"label"~descr:(Md.plain"Declaration label (uncapitalized kind & name)")~data:(moduleJstring)~get:(fun(decl,_)->Pretty_utils.to_stringpp_declarationdecl)modellet()=States.column~name:"source"~descr:(Md.plain"Source location")~data:(modulePosition)~get:(fun(decl,_)->fst@@loc_of_declarationdecl)modelletarray=States.register_array~package~name:"declAttributes"~descr:(Md.plain"Declaration attributes")~key:snd~keyName:"decl"~keyType:Decl.jtype~iter:iter_declaration~add_reload_hook:ast_update_hookmodelletupdate(d,s)=matchdwith|SGAnnotgawhennot@@GAnnotRoots.is_rootga->()|_->States.updatearray(d,s)let()=Decl.hookupdateend(* -------------------------------------------------------------------------- *)(* --- Decl Printer --- *)(* -------------------------------------------------------------------------- *)letprint_global_astglobal=letstacked_libc=Kernel.PrintLibc.get()intryifnotstacked_libcthenKernel.PrintLibc.settrue;letprinter=PrinterTag.(with_unfold_precond(fun_->true)pp_global)inletast=Jbuffer.to_jsonprinterglobalinifnotstacked_libcthenKernel.PrintLibc.setfalse;astwitherr->ifnotstacked_libcthenKernel.PrintLibc.setfalse;raiseerrlet()=Request.register~package~kind:`GET~name:"printDeclaration"~descr:(Md.plain"Prints an AST Declaration")~signals:[ast_changed_signal]~input:(moduleDecl)~output:(moduleJtext)(fund->print_global_ast@@Printer_tag.definition_of_declarationd)(* -------------------------------------------------------------------------- *)(* --- Marker Attributes --- *)(* -------------------------------------------------------------------------- *)moduleMarkerKind=structopenPrinter_tagtypet=localizableletjtype=Data.declare~package~name:"markerKind"~descr:(Md.plain"Marker kind")(Junion[Jkey"STMT";Jkey"LFUN";Jkey"DFUN";Jkey"LVAR";Jkey"DVAR";Jkey"LVAL";Jkey"EXP";Jkey"TERM";Jkey"TYPE";Jkey"PROPERTY";Jkey"DECLARATION";])letto_json=function|PStmt_|PStmtStart_->`String"STMT"|PVDecl(_,Kglobal,vi)->`String(ifGlobals.Functions.memvithen"DFUN"else"DVAR")|PVDecl_->`String"DVAR"|PTermLval(_,_,_,(TVar{lv_origin=Somevi},TNoOffset))|PLval(_,_,(Varvi,NoOffset))->`String(ifGlobals.Functions.memvithen"LFUN"else"LVAR")|PLval_->`String"LVAL"|PExp_->`String"EXP"|PTermLval_->`String"TERM"|PType_->`String"TYPE"|PIP_->`String"PROPERTY"|PGlobal_->`String"DECLARATION"endmoduleMarkerAttributes=structopenPrinter_tagletglobal_annotation_label_kindshort=function|Dfun_or_pred({l_type=None},_)->ifshortthen"Pred"else"Predicate"|Dfun_or_pred_->ifshortthen"LFun"else"Logic Function"|Dinvariant_->ifshortthen"Inv"else"Invariant"|Dtype_annot_->ifshortthen"TInv"else"Type Invariant"|Daxiomatic_->ifshortthen"Ax"else"Axiomatic"|Dmodule_->ifshortthen"Mod"else"Module"|Dlemma_->"Lemma"|Dextended_->ifshortthen"Ext"else"Extension"|Dvolatile_->ifshortthen"Vol"else"Volatile"|Dtype_->ifshortthen"LType"else"Logic Type"|Dmodel_annot_->"Model"letlabel_kind~shortm=matchvarinfo_of_localizablemwith|Somevi->ifGlobals.Functions.memvithen"Function"elseifvi.vglobthenifshortthen"Global"else"Global Variable"elseifvi.vformalthenifshortthen"Formal"else"Formal Parameter"elseifvi.vtempthenifshortthen"Temp"else"Temporary Variable (generated)"elseifshortthen"Local"else"Local Variable"|None->matchmwith|PStmt_|PStmtStart_->ifshortthen"Stmt"else"Statement"|PLval_->ifshortthen"Lval"else"L-value"|PTermLval_->ifshortthen"Lval"else"ACSL L-value"|PVDecl_->assertfalse|PExp_->ifshortthen"Expr"else"Expression"|PIP_->ifshortthen"Prop"else"Property"|PGlobal(GType_|GCompTag_|GEnumTag_|GEnumTagDecl_)|PType_->"Type"|PGlobal(GAnnot(ga,_))->global_annotation_label_kindshortga|PGlobal_->ifshortthen"Decl"else"Declaration"letdescr_localizablefmt=function|PGlobal(GType(ti,_))->PrinterTag.pp_typfmt(Cil_const.mk_tnamedti)|PGlobal(GCompTag(ci,_)|GCompTagDecl(ci,_))->PrinterTag.pp_typfmt(Cil_const.mk_tcompci)|PGlobal(GEnumTag(ei,_)|GEnumTagDecl(ei,_))->PrinterTag.pp_typfmt(Cil_const.mk_tenumei)|g->pp_localizablefmtgletmodel=States.model()let()=States.column~name:"kind"~descr:(Md.plain"Marker kind (key)")~data:(moduleMarkerKind)~get:fstmodellet()=States.option~name:"scope"~descr:(Md.plain"Marker Scope (where it is printed in)")~data:(moduleDecl)~get:(fun(tag,_)->declaration_of_localizabletag)modellet()=States.option~name:"definition"~descr:(Md.plain"Marker's Target Definition (when applicable)")~data:(moduleMarker)~get:(fun(tag,_)->definition_of_localizabletag)modellet()=States.column~name:"labelKind"~descr:(Md.plain"Marker kind label")~data:(moduleJalpha)~get:(fun(tag,_)->label_kind~short:truetag)modellet()=States.column~name:"titleKind"~descr:(Md.plain"Marker kind title")~data:(moduleJalpha)~get:(fun(tag,_)->label_kind~short:falsetag)modellet()=States.option~name:"name"~descr:(Md.plain"Marker identifier (when applicable)")~data:(moduleJalpha)~get:(fun(tag,_)->Printer_tag.name_of_localizabletag)modellet()=States.column~name:"descr"~descr:(Md.plain"Marker description")~data:(moduleJstring)~get:(fun(tag,_)->Rich_text.to_stringdescr_localizabletag)modellet()=letget(tag,_)=letpos=fst(Printer_tag.loc_of_localizabletag)inifCil_datatype.Position.(equalunknownpos)thenNoneelseSomeposinStates.option~name:"sloc"~descr:(Md.plain"Source location")~data:(modulePosition)~getmodelletarray=States.register_array~package~name:"markerAttributes"~descr:(Md.plain"Marker attributes")~key:snd~keyName:"marker"~keyType:Marker.jtype~iter:Marker.iter~add_reload_hook:ast_update_hookmodellet()=Marker.hook(States.updatearray)end(* -------------------------------------------------------------------------- *)(* --- Functions --- *)(* -------------------------------------------------------------------------- *)let()=Request.register~package~kind:`GET~name:"getMainFunction"~descr:(Md.plain"Get the current 'main' function.")~input:(moduleJunit)~output:(moduleJoption(Decl))beginfun()->trySome(SFunction(fst@@Globals.entry_point()))withGlobals.No_such_entry_point_->Noneendlet()=Request.register~package~kind:`GET~name:"getFunctions"~descr:(Md.plain"Collect all functions in the AST")~input:(moduleJunit)~output:(moduleJlist(Decl))beginfun()->letpool=ref[]inGlobals.Functions.iter(funkf->pool:=Printer_tag.SFunctionkf::!pool);List.rev!poolendmoduleFunctions=structletkeykf=Printf.sprintf"kf#%d"(Kernel_function.get_idkf)letsignaturekf=letg=Kernel_function.get_globalkfinletlibc=Kernel.PrintLibc.get()intryifnotlibcthenKernel.PrintLibc.settrue;lettxt=Rich_text.to_stringPrinter_tag.pp_localizable(PGlobalg)inifnotlibcthenKernel.PrintLibc.setfalse;ifKernel_function.is_entry_pointkfthen(txt^" /* main */")elsetxtwitherr->ifnotlibcthenKernel.PrintLibc.setfalse;raiseerrletis_builtinkf=Cil_builtins.has_fc_builtin_attr(Kernel_function.get_vikf)letis_externkf=letvi=Kernel_function.get_vikfinvi.vstorage=Externletiterf=Globals.Functions.iter(funkf->letname=Kernel_function.get_namekfinifnot(Ast_info.start_with_frama_c_builtinname)thenfkf)letarray:kernel_functionStates.array=beginletmodel=States.model()inStates.columnmodel~name:"decl"~descr:(Md.plain"Declaration Tag")~data:(moduleDecl)~get:(funkf->Printer_tag.SFunctionkf);States.columnmodel~name:"name"~descr:(Md.plain"Name")~data:(moduleData.Jalpha)~get:Kernel_function.get_name;States.columnmodel~name:"signature"~descr:(Md.plain"Signature")~data:(moduleData.Jstring)~get:signature;States.columnmodel~name:"main"~descr:(Md.plain"Is the function the main entry point")~data:(moduleData.Jbool)~default:false~get:Kernel_function.is_entry_point;States.columnmodel~name:"defined"~descr:(Md.plain"Is the function defined?")~data:(moduleData.Jbool)~default:false~get:Kernel_function.is_definition;States.columnmodel~name:"stdlib"~descr:(Md.plain"Is the function from the Frama-C stdlib?")~data:(moduleData.Jbool)~default:false~get:Kernel_function.is_in_libc;States.columnmodel~name:"builtin"~descr:(Md.plain"Is the function a Frama-C builtin?")~data:(moduleData.Jbool)~default:false~get:is_builtin;States.columnmodel~name:"extern"~descr:(Md.plain"Is the function extern?")~data:(moduleData.Jbool)~default:false~get:is_extern;States.columnmodel~name:"sloc"~descr:(Md.plain"Source location")~data:(modulePosition)~get:(funkf->fst(Kernel_function.get_locationkf));States.register_arraymodel~package~key~name:"functions"~descr:(Md.plain"AST Functions")~iter~add_reload_hook:ast_update_hookendend(* -------------------------------------------------------------------------- *)(* --- Global variables --- *)(* -------------------------------------------------------------------------- *)moduleGlobalVars=structletkeyvi=Printf.sprintf"vi#%d"vi.vidlet_:varinfoStates.array=letmodel=States.model()inStates.columnmodel~name:"decl"~descr:(Md.plain"Declaration Tag")~data:(moduleDecl)~get:(funvi->Printer_tag.SGlobalvi);States.columnmodel~name:"name"~descr:(Md.plain"Name")~data:(moduleData.Jalpha)~get:(funvi->vi.vname);States.columnmodel~name:"type"~descr:(Md.plain"Type")~data:(moduleJstring)~get:(funvi->Rich_text.to_stringPrinter.pp_typvi.vtype);States.columnmodel~name:"stdlib"~descr:(Md.plain"Is the variable from the Frama-C stdlib?")~data:(moduleData.Jbool)~get:(funvi->Cil.is_in_libcvi.vattr);States.columnmodel~name:"extern"~descr:(Md.plain"Is the variable extern?")~data:(moduleData.Jbool)~get:(funvi->vi.vstorage=Extern);States.columnmodel~name:"const"~descr:(Md.plain"Is the variable const?")~data:(moduleData.Jbool)~get:(funvi->Cil.isGlobalInitConstvi);States.columnmodel~name:"volatile"~descr:(Md.plain"Is the variable volatile?")~data:(moduleData.Jbool)~get:(funvi->Ast_types.is_volatilevi.vtype);States.columnmodel~name:"ghost"~descr:(Md.plain"Is the variable ghost?")~data:(moduleData.Jbool)~get:(funvi->Ast_types.is_ghostvi.vtype);States.columnmodel~name:"init"~descr:(Md.plain"Is the variable explicitly initialized?")~data:(moduleData.Jbool)~get:(funvi->Option.is_some(Globals.Vars.findvi).init);States.columnmodel~name:"source"~descr:(Md.plain"Is the variable in the source code?")~data:(moduleData.Jbool)~get:(funvi->vi.vsource);States.columnmodel~name:"sloc"~descr:(Md.plain"Source location")~data:(modulePosition)~get:(funvi->fstvi.vdecl);States.register_arraymodel~package~key~name:"globals"~descr:(Md.plain"AST global variables")~iter:(funf->Globals.Vars.iter(funvi_init->fvi))~add_reload_hook:ast_update_hookend(* -------------------------------------------------------------------------- *)(* --- Marker Information --- *)(* -------------------------------------------------------------------------- *)moduleInformation=structtypeinfo={id:string;rank:int;label:string;(* short name *)title:string;(* full title name *)descr:string;(* description for information values *)enable:unit->bool;pretty:Format.formatter->Printer_tag.localizable->unit}(* Info markers serialization *)moduleS=structtypet=(info*Jtext.t)letjtype=Package.(Jrecord["id",Jstring;"label",Jstring;"title",Jstring;"descr",Jstring;"text",Jtext.jtype;])letof_json_=failwith"Information.Info"letto_json(info,text)=`Assoc["id",`Stringinfo.id;"label",`Stringinfo.label;"title",`Stringinfo.title;"descr",`Stringinfo.descr;"text",text;]end(* Info markers registry *)letrankId=ref0letregistry:(string,info)Hashtbl.t=Hashtbl.create0letjtextppmarker=tryletbuffer=Jbuffer.create()inletfmt=Jbuffer.formatterbufferinppfmtmarker;Format.pp_print_flushfmt();Jbuffer.contentsbufferwithNot_found->`Nullletrank({rank},_)=rankletby_rankab=Stdlib.compare(ranka)(rankb)letget_informationtgt=letinfos=ref[]inHashtbl.iter(fun_info->ifinfo.enable()thenmatchtgtwith|None->infos:=(info,`Null)::!infos|Somemarker->lettext=jtextinfo.prettymarkerinifnot(Jbuffer.is_emptytext)theninfos:=(info,text)::!infos)registry;List.sortby_rank!infosletsignal=Request.signal~package~name:"getInformationUpdate"~descr:(Md.plain"Updated AST information")letupdate()=Request.emitsignalletregister~id~label~title?(descr=title)?(enable=fun_->true)pretty=letrank=incrrankId;!rankIdinletinfo={id;rank;label;title;descr;enable;pretty}inifHashtbl.memregistryidthen(letmsg=Format.sprintf"Server.Kernel_ast.register_info: duplicate %S"idinraise(Invalid_argumentmsg));Hashtbl.addregistryidinfoendlet()=Request.register~package~kind:`GET~name:"getInformation"~descr:(Md.plain"Get available information about markers. \
When no marker is given, returns all kinds \
of information (with empty `descr` field).")~input:(moduleJoption(Marker))~output:(moduleJlist(Information.S))~signals:[Information.signal]Information.get_information(* -------------------------------------------------------------------------- *)(* --- Default Kernel Information --- *)(* -------------------------------------------------------------------------- *)let()=Information.register~id:"kernel.ast.location"~label:"Location"~title:"Source file location"beginfunfmtloc->letpos=fst@@Printer_tag.loc_of_localizablelocinifFilepath.is_emptypos.pos_paththenraiseNot_found;Filepath.pp_posfmtposendlet()=Information.register~id:"kernel.ast.varinfo"~label:"Var"~title:"Variable Information"beginfunfmtloc->matchlocwith|PLval(_,_,(Varx,NoOffset))|PVDecl(_,_,x)->ifnotx.vreferencedthenFormat.pp_print_stringfmt"unused ";beginmatchx.vstoragewith|NoStorage->()|Extern->Format.pp_print_stringfmt"extern "|Static->Format.pp_print_stringfmt"static "|Register->Format.pp_print_stringfmt"register "end;ifx.vghostthenFormat.pp_print_stringfmt"ghost ";ifx.vaddrofthenFormat.pp_print_stringfmt"aliased ";ifx.vformalthenFormat.pp_print_stringfmt"formal"elseifx.vglobthenFormat.pp_print_stringfmt"global"elseifx.vtempthenFormat.pp_print_stringfmt"temporary"elseFormat.pp_print_stringfmt"local";|_->raiseNot_foundendlet()=Information.register~id:"kernel.ast.typeinfo"~label:"Type"~title:"Type of C/ASCL expression"beginfunfmtloc->letopenPrinterinmatchlocwith|PExp(_,_,e)->pp_typfmt(Cil.typeOfe)|PLval(_,_,lval)->pp_typfmt(Cil.typeOfLvallval)|PTermLval(_,_,_,lv)->pp_logic_typefmt(Cil.typeOfTermLvallv)|PVDecl(_,_,vi)->pp_typfmtvi.vtype|_->raiseNot_foundendlet()=Information.register~id:"kernel.ast.typedef"~label:"Typedef"~title:"Type Definition"beginfunfmtloc->matchlocwith|PType({tnode=TNamed_}asty)|PGlobal(GType({ttype=ty},_))->beginlettdef=Ast_types.unrolltyinmatchPrinter_tag.definition_of_typetdefwith|Somemarker->lettag=Marker.indexmarkerinFormat.fprintffmt"@{<%s>%a@}"tagPrinter.pp_typtdef|None->PrinterTag.pp_typfmttdefend|_->raiseNot_foundendlet()=Information.register~id:"kernel.ast.typesizeof"~label:"Sizeof"~title:"Size of a C-type or C-variable"beginfunfmtloc->lettyp=matchlocwith|PTypetyp->typ|PVDecl(_,_,vi)->vi.vtype|PGlobal(GType(ti,_))->ti.ttype|PGlobal(GCompTagDecl(ci,_)|GCompTag(ci,_))->Cil_const.mk_tcompci|PGlobal(GEnumTagDecl(ei,_)|GEnumTag(ei,_))->Cil_const.mk_tenumei|_->raiseNot_foundinletbits=tryCil.bitsSizeOftypwithCil.SizeOfError_->raiseNot_foundinletbytes=bits/8inletrbits=bitsmod8inifrbits>0thenifbytes>0thenFormat.fprintffmt"%d bytes + %d bits"bytesrbitselseFormat.fprintffmt"%d bits"rbitselseFormat.fprintffmt"%d bytes"bytesendlet()=Information.register~id:"kernel.ast.propertyStatus"~label:"Status"~title:"Property Consolidated Status"beginfunfmtloc->matchlocwith|PIPpropwhenProperty.has_statusprop->Property_status.Feedback.prettyfmt@@Property_status.Feedback.getprop|_->raiseNot_foundendlet()=Information.register~id:"kernel.ast.marker"~label:"Marker"~title:"Ivette marker (for debugging)"~enable:(fun_->Server_parameters.debug_atleast1)beginfunfmtloc->lettag=Marker.indexlocinFormat.fprintffmt"%S"tagendlet()=Server_parameters.Debug.add_hook_on_update(fun_->Information.update())(* -------------------------------------------------------------------------- *)(* --- Marker at a position --- *)(* -------------------------------------------------------------------------- *)letget_marker_at~file~line~col=iffile=""thenNoneelseletpos_path=Filepath.of_stringfileinletpos=Filepath.{pos_path;pos_lnum=line;pos_cnum=col;pos_bol=0;}inPrinter_tag.loc_to_localizable~precise_col:trueposlet()=letdescr=Md.plain"Returns the marker and function at a source file position, if any. \
Input: file path, line and column. \
File can be empty, in case no marker is returned."inletsignature=Request.signature~output:(moduleJoption(Marker))()inletget_file=Request.paramsignature~name:"file"~descr:(Md.plain"File path")(moduleJstring)inletget_line=Request.paramsignature~name:"line"~descr:(Md.plain"Line (1-based)")(moduleJint)inletget_col=Request.paramsignature~name:"column"~descr:(Md.plain"Column (0-based)")(moduleJint)inRequest.register_sigsignature~package~descr~kind:`GET~name:"getMarkerAt"~signals:[ast_changed_signal](funrq()->get_marker_at~file:(get_filerq)~line:(get_linerq)~col:(get_colrq))(* -------------------------------------------------------------------------- *)(* --- Files --- *)(* -------------------------------------------------------------------------- *)letget_files()=letfiles=Kernel.Files.get()inList.map(funf->(f:Filepath.t:>string))fileslet()=Request.register~package~descr:(Md.plain"Get the currently analyzed source file names")~kind:`GET~name:"getFiles"~input:(moduleJunit)~output:(moduleJlist(Jstring))get_filesletset_filesfiles=lets=String.concat","filesinKernel.Files.As_string.setslet()=Request.register~package~descr:(Md.plain"Set the source file names to analyze.")~kind:`SET~name:"setFiles"~input:(moduleJlist(Jstring))~output:(moduleJunit)set_files(* -------------------------------------------------------------------------- *)(* --- Build a marker from an ACSL term --- *)(* -------------------------------------------------------------------------- *)letenvironment()=letopenLogic_typinginLenv.empty()|>append_pre_label|>append_here_labelletparse_exprenvkfstmtterm=letterm=Logic_parse_string.term~envkfterminletexp=Logic_to_c.term_to_expterminPrinter_tag.PExp(Somekf,Kstmtstmt,exp)letparse_lvalenvkfstmtterm=letterm=Logic_parse_string.term_lval~envkfterminletlval=Logic_to_c.term_lval_to_lvalterminPrinter_tag.PLval(Somekf,Kstmtstmt,lval)letbuild_markerparsemarkerterm=matchPrinter_tag.ki_of_localizablemarkerwith|Kglobal->Data.failure"No statement at selection point"|Kstmtstmt->letmoduleC=Logic_to_cinletmoduleParser=Logic_parse_stringinletkf()=Kernel_function.find_englobing_kfstmtintryparse(environment())(kf())stmttermwithNot_found|Parser.(Error_|Unbound_)|C.No_conversion->Data.failure"Invalid term"let()=letmoduleMd=Markdowninlets=Request.signature~output:(moduleMarker)()inletget_marker=Request.params~name:"stmt"~descr:(Md.plain"Marker position from where to localize the term")(moduleMarker)inletget_term=Request.params~name:"term"~descr:(Md.plain"ACSL term to parse")(moduleData.Jstring)inRequest.register_sig~packages~kind:`GET~name:"parseExpr"~descr:(Md.plain"Parse a C expression and returns the associated marker")(funrq()->build_markerparse_expr(get_markerrq)(get_termrq))let()=letmoduleMd=Markdowninlets=Request.signature~output:(moduleMarker)()inletget_marker=Request.params~name:"stmt"~descr:(Md.plain"Marker position from where to localize the term")(moduleMarker)inletget_term=Request.params~name:"term"~descr:(Md.plain"ACSL term to parse")(moduleData.Jstring)inRequest.register_sig~packages~kind:`GET~name:"parseLval"~descr:(Md.plain"Parse a C lvalue and returns the associated marker")(funrq()->build_markerparse_lval(get_markerrq)(get_termrq))(* -------------------------------------------------------------------------- *)