123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495(**************************************************************************)(* *)(* This file is part of WP plug-in of Frama-C. *)(* *)(* Copyright (C) 2007-2025 *)(* CEA (Commissariat a l'energie atomique et aux energies *)(* 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). *)(* *)(**************************************************************************)(* -------------------------------------------------------------------------- *)(* --- Region Memory Model --- *)(* -------------------------------------------------------------------------- *)openCil_typesopenCtypesopenLang.FopenMemoryopenSigmaopenMemMemorytypeprim=Intofc_int|Floatofc_float|Ptrtypekind=Singleofprim|Manyofprim|Garbledletpp_primfmt=function|Inti->Ctypes.pp_intfmti|Floatf->Ctypes.pp_floatfmtf|Ptr->Format.pp_print_stringfmt"ptr"letpp_kindfmt=function|Singlep->pp_primfmtp|Manyp->Format.fprintffmt"[%a]"pp_primp|Garbled->Format.pp_print_stringfmt"[bytes]"lettau_of_prim=function|Int_->Qed.Logic.Int|Floatf->Cfloat.tau_of_floatf|Ptr->MemAddr.t_addr(* -------------------------------------------------------------------------- *)(* --- Region Analysis Proxy --- *)(* -------------------------------------------------------------------------- *)moduletypeRegionProxy=sigtyperegionvalid:region->intvalof_id:int->regionoptionvalpretty:Format.formatter->region->unitvalkind:region->kindvalname:region->stringoptionvalcvar:varinfo->regionoptionvalfield:region->fieldinfo->regionoptionvalshift:region->c_object->regionoptionvalpoints_to:region->regionoptionvalliteral:eid:int->Cstring.cst->regionoptionvalseparated:region->region->boolvalincluded:region->region->boolvalfootprint:region->regionlistend(* -------------------------------------------------------------------------- *)(* --- Region Memory Model --- *)(* -------------------------------------------------------------------------- *)moduleMake(R:RegionProxy)(M:Model)(L:MemLoader.Modelwithtypeloc=M.loc)=structtyperegion=R.regionletdatatype="MemRegion.Make"(* For projectification. Must be unique among models. *)letconfigure=M.configureletconfigure_ia=M.configure_ialethypotheses=M.hypothesesmoduleChunk=structletself="MemRegion.Chunk"typedata=Valueofprim|Arrayofprim|ValInit|ArrInittypet={data:data;region:R.region}letpp_datafmt=function|Valuep->Format.fprintffmt"µ%a"pp_primp|Arrayp->Format.fprintffmt"µ%a[]"pp_primp|ValInit->Format.pp_print_stringfmt"µinit"|ArrInit->Format.pp_print_stringfmt"µinit[]"lethash{data;region}=Hashtbl.hash(data,R.idregion)letequalab=Stdlib.(=)a.datab.data&&R.ida.region=R.idb.regionletcompareab=letcmp=Stdlib.comparea.datab.datainifcmp<>0thencmpelseInt.compare(R.ida.region)(R.idb.region)letprettyfmt{data;region}=Format.fprintffmt"%a@%03d"pp_datadata(R.idregion)lettau_of_chunk{data}=matchdatawith|Valuep->tau_of_primp|ValInit->Qed.Logic.Bool|Arrayp->Qed.Logic.Array(MemAddr.t_addr,tau_of_primp)|ArrInit->Qed.Logic.Array(MemAddr.t_addr,Qed.Logic.Bool)letbasename_of_chunkc=matchc.datawith|ValInit->"Vinit"|ArrInit->"Minit"|Arrayp->Format.asprintf"M%04x_%a"(R.idc.region)pp_primp|Valuep->matchR.namec.regionwith|Somea->a|None->Format.asprintf"V%04x_%a"(R.idc.region)pp_primpletis_initc=matchc.datawith|ValInit|ArrInit->true|Array_|Value_->falseletis_primaryc=matchc.datawith|Value_->true|ValInit|ArrInit|Array_->falseletis_framed_=falseendmoduleState=Sigma.Make(Chunk)(* -------------------------------------------------------------------------- *)(* --- Region Loader --- *)(* -------------------------------------------------------------------------- *)moduleLOADER=structletname="MemRegion.LOADER"typeloc=|Null|RawofM.loc|LocofM.loc*regionletprettyfmt(l:loc)=matchlwith|Null->M.prettyfmtM.null|Rawl->M.prettyfmtl|Loc(l,r)->Format.fprintffmt"%a@%a"M.prettylR.prettyrletmakea=functionNone->Rawa|Somer->Loc(a,r)letloc=functionNull->M.null|Rawa|Loc(a,_)->aletreg=functionNull|Raw_->None|Loc(_,r)->Somerletrfoldf=functionNull|Raw_->None|Loc(_,r)->fr(* ---------------------------------------------------------------------- *)(* --- Utilities on locations --- *)(* ---------------------------------------------------------------------- *)letlocalizedaction=function|Null->Warning.error~source:"MemRegion""Attempt to %s at NULL"action|Rawa->Warning.error~source:"MemRegion""Attempt to %s without region (%a)"actionM.prettya|Loc(l,r)->l,rletsizeofty=L.sizeoftyletto_addrl=M.pointer_val(locl)letlastsigmatyl=L.lastsigmaty(locl)letfieldlfd=make(M.field(locl)fd)(rfold(funr->R.fieldrfd)l)letofieldlfd=Option.map(funr->Loc(M.field(locl)fd,r))@@rfold(funr->R.fieldrfd)lletshiftlobjofs=make(M.shift(locl)objofs)(rfold(funr->R.shiftrobj)l)letfreshl=letl0,r=localized"quantify loc"linletxs,l1=L.freshl0inxs,Loc(l1,r)letseparatedpnp'n'=L.separated(locp)n(locp')n'leteqmemchunkm0m1ln=matchSigma.ckindchunkwith|State.Mu{data=ValInit|Value_}->p_equalm0m1|State.Mu{data=ArrInit|Array_}->p_callf_eqmem[m0;m1;to_addrl;n]|_->L.eqmemchunkm0m1(locl)nletmemcpychunkm0l0m1l1n=matchSigma.ckindchunkwith|State.Mu{data=ValInit|Value_}->m1|State.Mu{data=ArrInit|Array_}->e_funf_memcpy[m0;to_addrl0;m1;to_addrl1;n]|_->L.memcpychunkm0(locl0)m1(locl1)n(* ---------------------------------------------------------------------- *)(* --- Load --- *)(* ---------------------------------------------------------------------- *)letto_region_pointerl=letl,r=localized"get region pointer"linR.idr,M.pointer_vallletof_region_pointerr_t=make(M.pointer_loct)(R.of_idr)letcheck_accessaction(p:prim)(q:prim)=ifStdlib.(<>)pqthenWarning.error~source:"MemRegion""Inconsistent %s (%a <> %a)"actionpp_primppp_primqletload_intsigmaiotaloc:term=letl,r=localized"load int"locinmatchR.kindrwith|Garbled->L.load_intsigmaiotal|Singlep->check_access"load"p(Intiota);State.valuesigma{data=Valuep;region=r}|Manyp->check_access"load"p(Intiota);e_get(State.valuesigma{data=Arrayp;region=r})(M.pointer_vall)letload_floatsigmafltloc:term=letl,r=localized"load float"locinmatchR.kindrwith|Garbled->L.load_floatsigmafltl|Singlep->check_access"load"p(Floatflt);State.valuesigma{data=Valuep;region=r}|Manyp->check_access"load"p(Floatflt);e_get(State.valuesigma{data=Arrayp;region=r})(M.pointer_vall)letload_pointersigmatyloc:loc=letl,r=localized"load pointer"locinmatchR.points_torwith|None->Warning.error~source:"MemRegion""Attempt to load pointer without points-to@\n\
(addr %a, region %a)"M.prettylR.prettyr|Some_asrp->letloc=matchR.kindrwith|Garbled->L.load_pointersigmatyl|Singlep->check_access"load"pPtr;M.pointer_loc@@State.valuesigma{data=Valuep;region=r}|Manyp->check_access"load"pPtr;M.pointer_loc@@e_get(State.valuesigma{data=Arrayp;region=r})(M.pointer_vall)inmakelocrp(* ---------------------------------------------------------------------- *)(* --- Store --- *)(* ---------------------------------------------------------------------- *)letstore_intsigmaiotalocv:Sigma.chunk*term=letl,r=localized"store int"locinmatchR.kindrwith|Garbled->L.store_intsigmaiotalv|Singlep->check_access"store"p(Intiota);State.chunk{data=Valuep;region=r},v|Manyp->check_access"store"p(Intiota);letrc=Chunk.{data=Arrayp;region=r}inState.chunkrc,e_set(State.valuesigmarc)(M.pointer_vall)vletstore_floatsigmafltlocv:Sigma.chunk*term=letl,r=localized"store float"locinmatchR.kindrwith|Garbled->L.store_floatsigmafltlv|Singlep->check_access"store"p(Floatflt);State.chunk{data=Valuep;region=r},v|Manyp->check_access"store"p(Floatflt);letrc=Chunk.{data=Arrayp;region=r}inState.chunkrc,e_set(State.valuesigmarc)(M.pointer_vall)vletstore_pointersigmatylocv:Sigma.chunk*term=letl,r=localized"store pointer"locinmatchR.kindrwith|Garbled->L.store_pointersigmatylv|Singlep->check_access"store"pPtr;State.chunk{data=Valuep;region=r},v|Manyp->check_access"store"pPtr;letrc=Chunk.{data=Arrayp;region=r}inState.chunkrc,e_set(State.valuesigmarc)(M.pointer_vall)v(* ---------------------------------------------------------------------- *)(* --- Init --- *)(* ---------------------------------------------------------------------- *)letload_init_atomsigmaobjloc:term=letl,r=localized"init atom"locinmatchR.kindrwith|Garbled->L.load_init_atomsigmaobjl|Single_->State.valuesigma{data=ValInit;region=r}|Many_->e_get(State.valuesigma{data=ArrInit;region=r})(M.pointer_vall)letstore_init_atomsigmaobjlocv:Sigma.chunk*term=letl,r=localized"init atom"locinmatchR.kindrwith|Garbled->L.store_init_atomsigmaobjlv|Single_->State.chunk{data=ValInit;region=r},v|Many_->letrc=Chunk.{data=ArrInit;region=r}inState.chunkrc,e_set(State.valuesigmarc)(M.pointer_vall)v(* ---------------------------------------------------------------------- *)(* --- Footprints --- *)(* ---------------------------------------------------------------------- *)letlfootprint~initobjl=ifinitthenL.init_footprintobjlelseL.value_footprintobjlletrecfootprint~initobjloc=matchlocwith|Null->lfootprint~initobjM.null|Rawl->lfootprint~initobjl|Loc(l,r)->matchobjwith|C_comp{cfields=None}->Domain.empty|C_comp{cfields=Somefds}->List.fold_left(fundomfd->letobj=Ctypes.object_offd.ftypeinmatchofieldlocfdwith|None->dom|Someloc->Domain.uniondom(footprint~initobjloc))Domain.emptyfds|C_array{arr_element=elt}->letobj=object_ofeltinfootprint~initobj(shiftlocobje_zero)|C_int_|C_float_|C_pointer_->matchR.kindrwith|Garbled->lfootprint~initobjl|Singlep->letdata=Chunk.(ifinitthenValInitelseValuep)inState.singleton{data;region=r}|Manyp->letdata=Chunk.(ifinitthenArrInitelseArrayp)inState.singleton{data;region=r}letvalue_footprint=footprint~init:falseletinit_footprint=footprint~init:trueendtypeloc=LOADER.loctypesegment=locrlocletpretty=LOADER.prettyincludeMemLoader.Make(LOADER)letlookup=M.lookup(*TODO: lookups in MemRegion *)letupdates=M.updates(*TODO: updates in MemRegion *)(* {2 Memory Model API} *)letvarsl=M.vars@@LOADER.loclletoccursxl=M.occursx@@LOADER.loclletnull=LOADER.Nullletliteral~eid:eidstr=LOADER.make(M.literal~eidstr)(R.literal~eidstr)letcvarv=LOADER.make(M.cvarv)(R.cvarv)letfield=LOADER.fieldletshift=LOADER.shiftletpointer_loct=LOADER.Raw(M.pointer_loct)letpointer_vall=M.pointer_val@@LOADER.loclletbase_addrl=LOADER.Raw(M.base_addr@@LOADER.locl)letbase_offsetl=M.base_offset@@LOADER.loclletblock_lengthsigmaobjl=M.block_lengthsigmaobj@@LOADER.loclletis_null=functionLOADER.Null->p_true|Rawl|Loc(l,_)->M.is_nulllletloc_of_intobjt=LOADER.Raw(M.loc_of_intobjt)letint_of_lociotal=M.int_of_lociota@@LOADER.loclletcastconvl=letl0=LOADER.loclinletr0=LOADER.reglinLOADER.make(M.castconvl0)r0letloc_eqab=M.loc_eq(LOADER.loca)(LOADER.locb)letloc_ltab=M.loc_lt(LOADER.loca)(LOADER.locb)letloc_neqab=M.loc_neq(LOADER.loca)(LOADER.locb)letloc_leqab=M.loc_leq(LOADER.loca)(LOADER.locb)letloc_diffobjab=M.loc_diffobj(LOADER.loca)(LOADER.locb)letrloc=function|Rloc(obj,l)->Rloc(obj,LOADER.locl)|Rrange(l,obj,inf,sup)->Rrange(LOADER.locl,obj,inf,sup)letrloc_region=functionRloc(_,l)|Rrange(l,_,_,_)->LOADER.reglletvalidsigmaacsr=M.validsigmaacs@@rlocrletinvalidsigmar=M.invalidsigma(rlocr)letincluded(a:segment)(b:segment)=matchrloc_regiona,rloc_regionbwith|Somera,SomerbwhenR.separatedrarb->p_false|_->M.included(rloca)(rlocb)letseparated(a:segment)(b:segment)=matchrloc_regiona,rloc_regionbwith|Somera,SomerbwhenR.separatedrarb->p_true|_->M.separated(rloca)(rlocb)letalloc=M.allocletscope=M.scopeletglobal=M.globalletframesigma=letpool=ref@@M.framesigmainletassumep=pool:=p::!poolinSigma.iter(funcm->matchSigma.ckindcwith|State.Mu{data}->beginmatchdatawith|ValuePtr->assume@@globalsigma(e_varm)|ArrayPtr->assume@@MemMemory.framed(e_varm)|ValInit|ArrInit|Value_|Array_->()end|_->())sigma;!poolletis_well_formedsigma=letpool=ref@@[M.is_well_formedsigma]inletassumep=pool:=p::!poolinSigma.iter(funcm->matchSigma.ckindcwith|State.Mu{data}->beginmatchdatawith|ValInit|ArrInit->()|Value(Intiota)->assume@@Cint.rangeiota(e_varm)|Array(Intiota)->leta=Lang.freshvar~basename:"p"@@Lang.t_addr()inletb=e_get(e_varm)(e_vara)inassume@@p_forall[a](Cint.rangeiotab)|Value(Float_|Ptr)|Array(Float_|Ptr)->()end|_->())sigma;p_conj!poolend