123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932(* Js_of_ocaml compiler
* http://www.ocsigen.org/js_of_ocaml/
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; 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, with linking exception;
* either version 2.1 of the License, or (at your option) any later version.
*
* This program 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.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)(*XXX
Patterns:
=> loops should avoid absorbing the whole continuation...
(detect when the continuation does not loop anymore and close
the loop at this point)
=> should have special code for switches that include the preceding
if statement when possible
=> if e1 then {if e2 then P else Q} else {if e3 then P else Q}
=> if e then return e1; return e2
=> if e then var x = e1; else var x = e2;
=> while (true) {.... if (e) continue; break; }
- CLEAN UP!!!
*)open!Stdlibletdebug=Debug.find"gen"lettimes=Debug.find"times"openCodemoduleJ=Javascript(****)letstring_of_sets=String.concat~sep:", "(List.map~f:Addr.to_string(Addr.Set.elementss))letreclist_group_recfglbmn=matchlwith|[]->List.rev((b,List.revm)::n)|a::r->letfa=fainifPoly.(fa=b)thenlist_group_recfgrb(ga::m)nelselist_group_recfgrfa[ga]((b,List.revm)::n)letlist_groupfgl=matchlwith|[]->[]|a::r->list_group_recfgr(fa)[ga][](* like [List.map] except that it calls the function with
an additional argument to indicate whether we're mapping
over the last element of the list *)letrecmap_lastfl=matchlwith|[]->assertfalse|[x]->[ftruex]|x::xs->ffalsex::map_lastfxs(****)moduleShare=structtype'aaux={strings:'aStringMap.t;applies:'aIntMap.t;prims:'aStringMap.t}letempty_aux={prims=StringMap.empty;strings=StringMap.empty;applies=IntMap.empty}typet={mutablecount:intaux;mutablevars:J.identaux;alias_prims:bool;alias_strings:bool;alias_apply:bool}letadd_stringst=letn=tryStringMap.findst.stringswithNot_found->0in{twithstrings=StringMap.adds(n+1)t.strings}letadd_primst=letn=tryStringMap.findst.primswithNot_found->0in{twithprims=StringMap.adds(n+1)t.prims}letadd_special_prim_if_existsst=ifPrimitive.existssthen{twithprims=StringMap.adds(-1)t.prims}elsetletadd_applyit=letn=tryIntMap.findit.applieswithNot_found->0in{twithapplies=IntMap.addi(n+1)t.applies}letadd_code_stringsshare=letshare=add_stringsshareinifConfig.Flag.use_js_string()thenshareelseadd_prim"caml_string_of_jsbytes"shareletadd_code_istringsshare=add_stringsshareletrecget_constantct=matchcwith|Strings->add_code_stringst|IStrings->add_code_istringst|Tuple(_,args,_)->Array.fold_leftargs~init:t~f:(funtc->get_constantct)|_->tletadd_argsargst=List.fold_leftargs~init:t~f:(funta->matchawith|Pcc->get_constantct|_->t)letget?alias_strings?(alias_prims=false)?(alias_apply=true){blocks;_}:t=letalias_strings=matchalias_stringswith|None->Config.Flag.use_js_string()|Somex->xinletcount=Addr.Map.fold(fun_blockshare->List.fold_leftblock.body~init:share~f:(funsharei->matchiwith|Let(_,Constantc)->get_constantcshare|Let(_,Apply(_,args,false))->add_apply(List.lengthargs)share|Let(_,Prim(Extern"%closure",[Pc(IStringname|Stringname)]))->letname=Primitive.resolvenameinletshare=ifPrimitive.existsnamethenadd_primnameshareelseshareinshare|Let(_,Prim(Externname,args))->letname=Primitive.resolvenameinletshare=ifPrimitive.existsnamethenadd_primnameshareelseshareinadd_argsargsshare|Let(_,Prim(_,args))->add_argsargsshare|_->share))blocksempty_auxinletcount=List.fold_left["caml_trampoline";"caml_trampoline_return";"caml_wrap_exception";"caml_list_of_js_array";"caml_exn_with_js_backtrace"]~init:count~f:(funaccx->add_special_prim_if_existsxacc)in{count;vars=empty_aux;alias_strings;alias_prims;alias_apply}letget_stringgenst=ifnott.alias_stringsthengenselsetryletc=StringMap.findst.count.stringsinifc>1then(tryJ.EVar(StringMap.findst.vars.strings)withNot_found->letx=Var.fresh_n(Printf.sprintf"cst_%s"s)inletv=J.Vxint.vars<-{t.varswithstrings=StringMap.addsvt.vars.strings};J.EVarv)elsegenswithNot_found->gensletget_primgenst=lets=Primitive.resolvesinifnott.alias_primsthengenselsetryletc=StringMap.findst.count.primsinifc>1||c=-1then(tryJ.EVar(StringMap.findst.vars.prims)withNot_found->letx=Var.fresh_nsinletv=J.Vxint.vars<-{t.varswithprims=StringMap.addsvt.vars.prims};J.EVarv)elsegenswithNot_found->gensletget_applygennt=ifnott.alias_applythengennelsetryJ.EVar(IntMap.findnt.vars.applies)withNot_found->letx=Var.fresh_n(Printf.sprintf"caml_call%d"n)inletv=J.Vxint.vars<-{t.varswithapplies=IntMap.addnvt.vars.applies};J.EVarvendmoduleCtx=structtypet={blocks:blockAddr.Map.t;live:intarray;share:Share.t;debug:Parse_bytecode.Debug.t;exported_runtime:Code.Var.toption}letinitial~exported_runtimeblockslivesharedebug={blocks;live;share;debug;exported_runtime}endletvarx=J.EVar(J.Vx)letintn=J.ENum(J.Num.of_int32(Int32.of_intn))letint32n=J.ENum(J.Num.of_int32n)letto_intcx=J.EBin(J.Bor,cx,int0)letunsigned'x=J.EBin(J.Lsr,x,int0)letunsignedx=letpos_int32=matchxwith|J.ENumnum->(tryInt32.(J.Num.to_int32num>=0l)with_->false)|_->falseinifpos_int32thenxelseunsigned'xletone=int1letzero=int0letplus_intxy=matchx,ywith|J.ENumy,xwhenJ.Num.is_zeroy->x|x,J.ENumywhenJ.Num.is_zeroy->x|J.ENumx,J.ENumy->J.ENum(J.Num.addxy)|x,y->J.EBin(J.Plus,x,y)letboole=J.ECond(e,one,zero)(****)letsource_locationctx?afterpc=matchParse_bytecode.Debug.find_locctx.Ctx.debug?afterpcwith|Somepi->J.Pipi|None->J.N(****)letfloat_constf=J.ENum(J.Num.of_floatf)lets_varname=J.EVar(J.identname)letruntime_functxname=matchctx.Ctx.exported_runtimewith|Someruntime->J.EDot(J.EVar(J.Vruntime),name)|None->s_varnameletstr_jss=J.EStr(s,`Bytes)letecallfargsloc=J.ECall(f,List.mapargs~f:(funx->x,`Not_spread),loc)(****)(*
Some variables are constant: x = 1
Some may change after effectful operations : x = y[z]
There can be at most one effectful operations in the queue at once
let (e, expr_queue) = ... in
flush_queue expr_queue e
*)letconst_p=0letmutable_p=1letmutator_p=2letflush_p=3letor_ppq=maxpqletis_mutablep=p>=mutable_pletkindk=matchkwith|`Pure->const_p|`Mutable->mutable_p|`Mutator->mutator_pletocaml_string~ctx~locs=ifConfig.Flag.use_js_string()thenselseletp=Share.get_prim(runtime_functx)"caml_string_of_jsbytes"ctx.Ctx.shareinecallp[s]locletrecconstant_rec~ctxxlevelinstrs=matchxwith|Strings->lete=Share.get_stringstr_jssctx.Ctx.shareinlete=ocaml_string~ctx~loc:J.Neine,instrs|IStrings->Share.get_stringstr_jssctx.Ctx.share,instrs|Floatf->float_constf,instrs|Float_arraya->(Mlvalue.Array.make~tag:Obj.double_array_tag~args:(Array.to_list(Array.mapa~f:float_const)),instrs)|Int64i->letp=Share.get_prim(runtime_functx)"caml_int64_create_lo_mi_hi"ctx.Ctx.shareinletlo=int(Int64.to_intiland0xffffff)andmi=int(Int64.to_int(Int64.shift_righti24)land0xffffff)andhi=int(Int64.to_int(Int64.shift_righti48)land0xffff)inecallp[lo;mi;hi]J.N,instrs|Tuple(tag,a,_)->(letconstant_max_depth=Config.Param.constant_max_depth()inletrecdetect_listnacc=function|Tuple(0,[|x;l|],_)->detect_list(succn)(x::acc)l|Int0l->ifn>constant_max_depththenSomeaccelseNone|_->Noneinmatchdetect_list0[]xwith|Someelts_rev->letarr,instrs=List.fold_leftelts_rev~init:([],instrs)~f:(fun(arr,instrs)elt->letjs,instrs=constant_rec~ctxeltlevelinstrsinSomejs::arr,instrs)inletp=Share.get_prim(runtime_functx)"caml_list_of_js_array"ctx.Ctx.shareinecallp[J.EArrarr]J.N,instrs|None->letsplit=level=constant_max_depthinletlevel=ifsplitthen0elselevel+1inletl,instrs=List.fold_left(Array.to_lista)~init:([],instrs)~f:(fun(l,instrs)cc->letjs,instrs=constant_rec~ctxcclevelinstrsinjs::l,instrs)inletl,instrs=ifsplitthenList.fold_leftl~init:([],instrs)~f:(fun(acc,instrs)js->matchjswith|J.EArr_->letv=Code.Var.fresh_n"partial"inletinstrs=(J.Variable_statement[J.Vv,Some(js,J.N)],J.N)::instrsinJ.EVar(J.Vv)::acc,instrs|_->js::acc,instrs)elseList.revl,instrsinMlvalue.Block.make~tag~args:l,instrs)|Inti->int32i,instrsletconstant~ctxxlevel=letexpr,instr=constant_rec~ctxxlevel[]inexpr,List.revinstrtypequeue_elt={prop:int;cardinal:int;ce:J.expression;loc:J.location;deps:Code.Var.Set.t}letaccess_queuequeuex=tryletelt=List.assocxqueueinifelt.cardinal=1then(elt.prop,elt.ce),List.remove_assocxqueueelse((elt.prop,elt.ce),List.mapqueue~f:(function|x',eltwhenVar.equalxx'->x',{eltwithcardinal=predelt.cardinal}|x->x))withNot_found->(const_p,varx),queueletaccess_queue'~ctxqueuex=matchxwith|Pcc->letjs,instrs=constant~ctxc(Config.Param.constant_max_depth())inassert(List.is_emptyinstrs);(* We only have simple constants here *)(const_p,js),queue|Pvx->access_queuequeuexletaccess_queue_may_flushqueuevx=lettx,queue=access_queuequeuexinlet_,instrs,queue=List.fold_leftqueue~init:(Code.Var.Set.singletonv,[],[])~f:(fun(deps,instrs,queue)((y,elt)aseq)->ifCode.Var.Set.exists(funp->Code.Var.Set.mempdeps)elt.depsthen(Code.Var.Set.addydeps,(J.Variable_statement[J.Vy,Some(elt.ce,elt.loc)],elt.loc)::instrs,queue)elsedeps,instrs,eq::queue)ininstrs,(tx,List.revqueue)letshould_flushcondprop=cond<>const_p&&cond+prop>=flush_pletflush_queueexpr_queueprop(l:J.statement_list)=letinstrs,expr_queue=ifprop>=flush_pthenexpr_queue,[]elseList.partition~f:(fun(_,elt)->should_flushpropelt.prop)expr_queueinletinstrs=List.mapinstrs~f:(fun(x,elt)->J.Variable_statement[J.Vx,Some(elt.ce,elt.loc)],elt.loc)inList.rev_appendinstrsl,expr_queueletflush_allexpr_queuel=fst(flush_queueexpr_queueflush_pl)letenqueueexpr_queuepropxceloccardinalacc=letinstrs,expr_queue=ifConfig.Flag.compact()thenifis_mutablepropthenflush_queueexpr_queueprop[]else[],expr_queueelseflush_queueexpr_queueflush_p[]inletdeps=Js_simpl.get_variableCode.Var.Set.emptyceinletdeps=List.fold_leftexpr_queue~init:deps~f:(fundeps(x',elt)->ifCode.Var.Set.memx'depsthenCode.Var.Set.unionelt.depsdepselsedeps)ininstrs@acc,(x,{prop;ce;loc;cardinal;deps})::expr_queue(****)typestate={succs:(int,intlist)Hashtbl.t;backs:(int,Addr.Set.t)Hashtbl.t;preds:(int,int)Hashtbl.t;mutableloops:Addr.Set.t;mutableloop_stack:(Addr.t*(J.Label.t*boolref))list;mutablevisited_blocks:Addr.Set.t;mutableinterm_idx:int;ctx:Ctx.t;mutableblocks:Code.blockAddr.Map.t}letget_predsstpc=tryHashtbl.findst.predspcwithNot_found->0letincr_predsstpc=Hashtbl.replacest.predspc(get_predsstpc+1)letdecr_predsstpc=Hashtbl.replacest.predspc(get_predsstpc-1)letprotect_predsstpc=Hashtbl.replacest.predspc(get_predsstpc+1000000)letunprotect_predsstpc=Hashtbl.replacest.predspc(get_predsstpc-1000000)moduleDTree=struct(* This as to be kept in sync with the way we build conditionals
and switches! *)typecond=|IsTrue|CEqofint32|CLtofint32|CLeofint32type'at=|Ifofcond*'at*'at|Switchof(intlist*'at)array|Branchof'a|Emptyletnormalizea=a|>Array.to_list|>List.stable_sort~cmp:(fun(cont1,_)(cont2,_)->Poly.comparecont1cont2)|>list_groupfstsnd|>List.map~f:(fun(cont1,l1)->cont1,List.flattenl1)|>List.stable_sort~cmp:(fun(_,l1)(_,l2)->compare(List.lengthl1)(List.lengthl2))|>Array.of_listletbuild_ifb1b2=If(IsTrue,Branchb1,Branchb2)letbuild_switch(a:contarray):'at=letm=Config.Param.switch_max_case()inletai=Array.mapia~f:(funix->x,i)in(* group the contiguous cases with the same continuation *)letai:(Code.cont*intlist)array=Array.of_list(list_groupfstsnd(Array.to_listai))inletreclooplowup=letarray_norm:(Code.cont*intlist)array=normalize(Array.subai~pos:low~len:(up-low+1))inletarray_len=Array.lengtharray_norminifarray_len=1(* remaining cases all jump to the same branch *)thenBranch(fstarray_norm.(0))elsetry(* try to optimize when there are only 2 branch *)matcharray_normwith|[|(b1,[i1]);(b2,_l2)|]->If(CEq(Int32.of_inti1),Branchb1,Branchb2)|[|(b1,_l1);(b2,[i2])|]->If(CEq(Int32.of_inti2),Branchb2,Branchb1)|[|(b1,l1);(b2,l2)|]->letboundl1=matchl1,List.revl1with|min::_,max::_->min,max|_->assertfalseinletmin1,max1=boundl1inletmin2,max2=boundl2inifmax1<min2thenIf(CLt(Int32.of_intmax1),Branchb2,Branchb1)elseifmax2<min1thenIf(CLt(Int32.of_intmax2),Branchb1,Branchb2)elseraiseNot_found|_->raiseNot_foundwithNot_found->((* do we have to split again ? *)(* we count the number of cases, default/last case count for one *)letnbcases=ref1(* default case *)infori=0toarray_len-2donbcases:=!nbcases+List.length(sndarray_norm.(i))done;if!nbcases<=mthenSwitch(Array.maparray_norm~f:(fun(x,l)->l,Branchx))elseleth=(up+low)/2inletb1=looplowhandb2=loop(succh)upinletrange1=sndai.(h)andrange2=sndai.(succh)inmatchrange1,range2with|[],_|_,[]->assertfalse|_,lower_bound2::_->If(CLe(Int32.of_intlower_bound2),b2,b1))inletlen=Array.lengthaiiniflen=0thenEmptyelseloop0(len-1)letrecfold_contfbacc=matchbwith|If(_,b1,b2)->letacc=fold_contfb1accinletacc=fold_contfb2accinacc|Switcha->Array.fold_lefta~init:acc~f:(funacc(_,b)->fold_contfbacc)|Branch(pc,_)->fpcacc|Empty->accletnbcompa=letrecloopc=function|Empty->c|Branch_->c|If(_,a,b)->letc=succcinletc=loopcainletc=loopcbinc|Switcha->letc=succcinArray.fold_lefta~init:c~f:(funacc(_,b)->loopaccb)inloop0aendletfold_childrenblockspcfaccu=letblock=Addr.Map.findpcblocksinmatchblock.branchwith|Return_|Raise_|Stop->accu|Branch(pc',_)|Poptrap((pc',_),_)->fpc'accu|Pushtrap((pc1,_),_,(pc2,_),_)->letaccu=fpc1accuinletaccu=fpc2accuinaccu|Cond(_,cont1,cont2)->DTree.fold_contf(DTree.build_ifcont1cont2)accu|Switch(_,a1,a2)->leta1=DTree.build_switcha1anda2=DTree.build_switcha2inletaccu=DTree.fold_contfa1accuinletaccu=DTree.fold_contfa2accuinacculetrecbuild_graphstpcanc=ifnot(Addr.Set.mempcst.visited_blocks)then(st.visited_blocks<-Addr.Set.addpcst.visited_blocks;letanc=Addr.Set.addpcancinlets=Code.fold_childrenst.blockspcAddr.Set.addAddr.Set.emptyinletbacks=Addr.Set.intersancinHashtbl.addst.backspcbacks;lets=fold_childrenst.blockspc(funxl->x::l)[]inletsuccs=List.filters~f:(funpc->not(Addr.Set.mempcanc))inHashtbl.addst.succspcsuccs;Addr.Set.iter(funpc'->st.loops<-Addr.Set.addpc'st.loops)backs;List.itersuccs~f:(funpc'->build_graphstpc'anc);List.itersuccs~f:(funpc'->incr_predsstpc'))letrecdominance_frontier_recstpcvisitedgrey=letn=get_predsstpcinletv=tryAddr.Map.findpcvisitedwithNot_found->0inifv<nthenletv=v+1inletvisited=Addr.Map.addpcvvisitedinifv=nthenletgrey=Addr.Set.removepcgreyinlets=Hashtbl.findst.succspcinList.fold_rights~init:(visited,grey)~f:(funpc'(visited,grey)->dominance_frontier_recstpc'visitedgrey)elsevisited,ifv=1thenAddr.Set.addpcgreyelsegreyelsevisited,greyletdominance_frontierstpc=snd(dominance_frontier_recstpcAddr.Map.emptyAddr.Set.empty)letrecresolve_nodeintermpc=tryresolve_nodeinterm(fst(Addr.Map.findpcinterm))withNot_found->pcletresolve_nodesinterms=Addr.Set.fold(funpcs'->Addr.Set.add(resolve_nodeintermpc)s')sAddr.Set.empty(****)letrecvisitvisitedprevsmxl=ifnot(Var.Set.memxvisited)thenletvisited=Var.Set.addxvisitedinlety=Var.Map.findxminifCode.Var.comparexy=0thenvisited,None,lelseifVar.Set.memyprevthenlett=Code.Var.fresh()invisited,Some(y,t),(x,t)::lelseifVar.Set.memysthenletvisited,aliases,l=visitvisited(Var.Set.addxprev)smylinmatchaliaseswith|Some(a,b)whenCode.Var.compareax=0->visited,None,(b,a)::(x,y)::l|_->visited,aliases,(x,y)::lelsevisited,None,(x,y)::lelsevisited,None,lletvisit_allparamsargs=letm=Subst.build_mappingparamsargsinlets=List.fold_leftparams~init:Var.Set.empty~f:(funsx->Var.Set.addxs)inlet_,l=Var.Set.fold(funx(visited,l)->letvisited,_,l=visitvisitedVar.Set.emptysmxlinvisited,l)s(Var.Set.empty,[])inlletparallel_renamingparamsargscontinuationqueue=letl=List.rev(visit_allparamsargs)inList.fold_leftl~f:(funcontinuation(y,x)queue->letinstrs,((px,cx),queue)=access_queue_may_flushqueueyxinletst,queue=flush_queuequeuepx(instrs@[J.Variable_statement[J.Vy,Some(cx,J.N)],J.N])inst@continuationqueue)~init:continuationqueue(****)letapply_fun_rawctxfparams=letn=List.lengthparamsinJ.ECond(J.EBin(J.EqEq,J.EDot(f,"length"),intn),ecallfparamsJ.N,ecall(runtime_functx"caml_call_gen")[f;J.EArr(List.mapparams~f:(funx->Somex))]J.N)letgenerate_apply_functxn=letf'=Var.fresh_n"f"inletf=J.Vf'inletparams=Array.to_list(Array.initn~f:(funi->leta=Var.fresh_n(Printf.sprintf"a%d"i)inJ.Va))inletf'=J.EVarfinletparams'=List.mapparams~f:(funx->J.EVarx)inJ.EFun(None,f::params,[J.Statement(J.Return_statement(Some(apply_fun_rawctxf'params'))),J.N],J.N)letapply_functxfparamsloc=ifConfig.Flag.inline_callgen()thenapply_fun_rawctxfparamselselety=Share.get_apply(generate_apply_functx)(List.lengthparams)ctx.Ctx.shareinecally(f::params)loc(****)let_=List.iter~f:(fun(nm,nm')->Primitive.aliasnmnm')["%int_mul","caml_mul";"%int_div","caml_div";"%int_mod","caml_mod";"caml_int32_neg","%int_neg";"caml_int32_add","%int_add";"caml_int32_sub","%int_sub";"caml_int32_mul","%int_mul";"caml_int32_div","%int_div";"caml_int32_mod","%int_mod";"caml_int32_and","%int_and";"caml_int32_or","%int_or";"caml_int32_xor","%int_xor";"caml_int32_shift_left","%int_lsl";"caml_int32_shift_right","%int_asr";"caml_int32_shift_right_unsigned","%int_lsr";"caml_int32_of_int","%identity";"caml_int32_to_int","%identity";"caml_int32_of_float","caml_int_of_float";"caml_int32_to_float","%identity";"caml_int32_format","caml_format_int";"caml_int32_of_string","caml_int_of_string";"caml_int32_compare","caml_int_compare";"caml_nativeint_neg","%int_neg";"caml_nativeint_add","%int_add";"caml_nativeint_sub","%int_sub";"caml_nativeint_mul","%int_mul";"caml_nativeint_div","%int_div";"caml_nativeint_mod","%int_mod";"caml_nativeint_and","%int_and";"caml_nativeint_or","%int_or";"caml_nativeint_xor","%int_xor";"caml_nativeint_shift_left","%int_lsl";"caml_nativeint_shift_right","%int_asr";"caml_nativeint_shift_right_unsigned","%int_lsr";"caml_nativeint_of_int","%identity";"caml_nativeint_to_int","%identity";"caml_nativeint_of_float","caml_int_of_float";"caml_nativeint_to_float","%identity";"caml_nativeint_of_int32","%identity";"caml_nativeint_to_int32","%identity";"caml_nativeint_format","caml_format_int";"caml_nativeint_of_string","caml_int_of_string";"caml_nativeint_compare","caml_int_compare";"caml_nativeint_bswap","caml_int32_bswap";"caml_int64_of_int","caml_int64_of_int32";"caml_int64_to_int","caml_int64_to_int32";"caml_int64_of_nativeint","caml_int64_of_int32";"caml_int64_to_nativeint","caml_int64_to_int32";"caml_float_of_int","%identity";"caml_array_get_float","caml_array_get";"caml_floatarray_get","caml_array_get";"caml_array_get_addr","caml_array_get";"caml_array_set_float","caml_array_set";"caml_floatarray_set","caml_array_set";"caml_array_set_addr","caml_array_set";"caml_array_unsafe_get_float","caml_array_unsafe_get";"caml_floatarray_unsafe_get","caml_array_unsafe_get";"caml_array_unsafe_set_float","caml_array_unsafe_set";"caml_floatarray_unsafe_set","caml_array_unsafe_set";"caml_alloc_dummy_float","caml_alloc_dummy";"caml_make_array","%identity";"caml_ensure_stack_capacity","%identity";"caml_js_from_float","%identity";"caml_js_to_float","%identity"]letinternal_primitives=Hashtbl.create31letinternal_primname=tryHashtbl.findinternal_primitivesnamewithNot_found->Noneletregister_primnamekf=Primitive.registernamekNoneNone;Hashtbl.addinternal_primitivesname(Somef)letregister_un_primnamekf=register_primnamek(funlqueuectxloc->matchlwith|[x]->let(px,cx),queue=access_queue'~ctxqueuexinfcxloc,or_p(kindk)px,queue|_->assertfalse)letregister_un_prim_ctxnamekf=register_primnamek(funlqueuectxloc->matchlwith|[x]->let(px,cx),queue=access_queue'~ctxqueuexinfctxcxloc,or_p(kindk)px,queue|_->assertfalse)letregister_bin_primnamekf=register_primnamek(funlqueuectxloc->matchlwith|[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinfcxcyloc,or_p(kindk)(or_ppxpy),queue|_->assertfalse)letregister_tern_primnamef=register_primname`Mutator(funlqueuectxloc->matchlwith|[x;y;z]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinlet(pz,cz),queue=access_queue'~ctxqueuezinfcxcyczloc,or_pmutator_p(or_ppx(or_ppypz)),queue|_->assertfalse)letregister_un_math_primnameprim=register_un_primname`Pure(funcxloc->ecall(J.EDot(s_var"Math",prim))[cx]loc)letregister_bin_math_primnameprim=register_bin_primname`Pure(funcxcyloc->ecall(J.EDot(s_var"Math",prim))[cx;cy]loc)let_=register_un_prim_ctx"%caml_format_int_special"`Pure(functxcxloc->lets=J.EBin(J.Plus,str_js"",cx)inocaml_string~ctx~locs);register_bin_prim"caml_array_unsafe_get"`Mutable(funcxcy_->Mlvalue.Array.fieldcxcy);register_bin_prim"%int_add"`Pure(funcxcy_->to_int(plus_intcxcy));register_bin_prim"%int_sub"`Pure(funcxcy_->to_int(J.EBin(J.Minus,cx,cy)));register_bin_prim"%direct_int_mul"`Pure(funcxcy_->to_int(J.EBin(J.Mul,cx,cy)));register_bin_prim"%direct_int_div"`Pure(funcxcy_->to_int(J.EBin(J.Div,cx,cy)));register_bin_prim"%direct_int_mod"`Pure(funcxcy_->to_int(J.EBin(J.Mod,cx,cy)));register_bin_prim"%int_and"`Pure(funcxcy_->J.EBin(J.Band,cx,cy));register_bin_prim"%int_or"`Pure(funcxcy_->J.EBin(J.Bor,cx,cy));register_bin_prim"%int_xor"`Pure(funcxcy_->J.EBin(J.Bxor,cx,cy));register_bin_prim"%int_lsl"`Pure(funcxcy_->J.EBin(J.Lsl,cx,cy));register_bin_prim"%int_lsr"`Pure(funcxcy_->to_int(J.EBin(J.Lsr,cx,cy)));register_bin_prim"%int_asr"`Pure(funcxcy_->J.EBin(J.Asr,cx,cy));register_un_prim"%int_neg"`Pure(funcx_->to_int(J.EUn(J.Neg,cx)));register_bin_prim"caml_eq_float"`Pure(funcxcy_->bool(J.EBin(J.EqEq,cx,cy)));register_bin_prim"caml_neq_float"`Pure(funcxcy_->bool(J.EBin(J.NotEq,cx,cy)));register_bin_prim"caml_ge_float"`Pure(funcxcy_->bool(J.EBin(J.Le,cy,cx)));register_bin_prim"caml_le_float"`Pure(funcxcy_->bool(J.EBin(J.Le,cx,cy)));register_bin_prim"caml_gt_float"`Pure(funcxcy_->bool(J.EBin(J.Lt,cy,cx)));register_bin_prim"caml_lt_float"`Pure(funcxcy_->bool(J.EBin(J.Lt,cx,cy)));register_bin_prim"caml_add_float"`Pure(funcxcy_->J.EBin(J.Plus,cx,cy));register_bin_prim"caml_sub_float"`Pure(funcxcy_->J.EBin(J.Minus,cx,cy));register_bin_prim"caml_mul_float"`Pure(funcxcy_->J.EBin(J.Mul,cx,cy));register_bin_prim"caml_div_float"`Pure(funcxcy_->J.EBin(J.Div,cx,cy));register_un_prim"caml_neg_float"`Pure(funcx_->J.EUn(J.Neg,cx));register_bin_prim"caml_fmod_float"`Pure(funcxcy_->J.EBin(J.Mod,cx,cy));register_tern_prim"caml_array_unsafe_set"(funcxcycz_->J.EBin(J.Eq,Mlvalue.Array.fieldcxcy,cz));register_un_prim"caml_alloc_dummy"`Pure(fun__->J.EArr[]);register_un_prim"caml_obj_dup"`Mutable(funcxloc->J.ECall(J.EDot(cx,"slice"),[],loc));register_un_prim"caml_int_of_float"`Pure(funcx_loc->to_intcx);register_un_math_prim"caml_abs_float""abs";register_un_math_prim"caml_acos_float""acos";register_un_math_prim"caml_asin_float""asin";register_un_math_prim"caml_atan_float""atan";register_bin_math_prim"caml_atan2_float""atan2";register_un_math_prim"caml_ceil_float""ceil";register_un_math_prim"caml_cos_float""cos";register_un_math_prim"caml_exp_float""exp";register_un_math_prim"caml_floor_float""floor";register_un_math_prim"caml_log_float""log";register_bin_math_prim"caml_power_float""pow";register_un_math_prim"caml_sin_float""sin";register_un_math_prim"caml_sqrt_float""sqrt";register_un_math_prim"caml_tan_float""tan";register_un_prim"caml_js_from_bool"`Pure(funcx_->J.EUn(J.Not,J.EUn(J.Not,cx)));register_un_prim"caml_js_to_bool"`Pure(funcx_->to_intcx);register_tern_prim"caml_js_set"(funcxcycz_->J.EBin(J.Eq,J.EAccess(cx,cy),cz));register_bin_prim"caml_js_get"`Mutable(funcxcy_->J.EAccess(cx,cy));register_bin_prim"caml_js_delete"`Mutable(funcxcy_->J.EUn(J.Delete,J.EAccess(cx,cy)));register_bin_prim"caml_js_equals"`Mutable(funcxcy_->bool(J.EBin(J.EqEq,cx,cy)));register_bin_prim"caml_js_instanceof"`Pure(funcxcy_->bool(J.EBin(J.InstanceOf,cx,cy)));register_un_prim"caml_js_typeof"`Pure(funcx_->J.EUn(J.Typeof,cx))(* This is not correct when switching the js-string flag *)(* {[
register_un_prim "caml_jsstring_of_string" `Mutable (fun cx loc ->
J.ECall (J.EDot (cx, "toString"), [], loc));
register_bin_prim "caml_string_notequal" `Pure (fun cx cy _ ->
J.EBin (J.NotEqEq, cx, cy));
register_bin_prim "caml_string_equal" `Pure (fun cx cy _ ->
bool (J.EBin (J.EqEq, cx, cy)))
]}
*)(****)(* when raising ocaml exception and [improved_stacktrace] is enabled,
tag the ocaml exception with a Javascript error (that contain js stacktrace).
{[ throw e ]}
becomes
{[ throw (caml_exn_with_js_backtrace(e,false)) ]}
*)letthrow_statementctxcxkloc=match(k:[`Normal|`Reraise|`Notrace])with|_whennot(Config.Flag.improved_stacktrace())->[J.Throw_statementcx,loc]|`Notrace->[J.Throw_statementcx,loc]|`Normal->[(J.Throw_statement(ecall(runtime_functx"caml_exn_with_js_backtrace")[cx;bool(int1)]loc),loc)]|`Reraise->[(J.Throw_statement(ecall(runtime_functx"caml_exn_with_js_backtrace")[cx;bool(int0)]loc),loc)]letrectranslate_exprctxqueueloc_xelevel:_*J.statement_list=matchewith|Apply(x,l,true)->let(px,cx),queue=access_queuequeuexinletargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queuequeuexincx::args,or_ppropprop',queue)l~init:([],or_ppxmutator_p,queue)in(ecallcxargsloc,prop,queue),[]|Apply(x,l,false)->letargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queuequeuexincx::args,or_ppropprop',queue)l~init:([],mutator_p,queue)inlet(prop',f),queue=access_queuequeuexinletprop=or_ppropprop'inlete=apply_functxfargslocin(e,prop,queue),[]|Block(tag,a,array_or_not)->letcontents,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queuequeuexincx::args,or_ppropprop',queue)(Array.to_lista)~init:([],const_p,queue)inletx=matcharray_or_notwith|Array->Mlvalue.Array.make~tag~args:contents|NotArray|Unknown->Mlvalue.Block.make~tag~args:contentsin(x,prop,queue),[]|Field(x,n)->let(px,cx),queue=access_queuequeuexin(Mlvalue.Block.fieldcxn,or_ppxmutable_p,queue),[]|Closure(args,((pc,_)ascont))->letloc=source_locationctx~after:truepcinletclo=compile_closurectxcontinletclo=matchclowith|(st,J.N)::rem->(st,J.U)::rem|_->cloinletclo=J.EFun(None,List.mapargs~f:(funv->J.Vv),clo,loc)in(clo,flush_p,queue),[]|Constantc->letjs,instrs=constant~ctxclevelin(js,const_p,queue),instrs|Prim(Extern"debugger",_)->letins=ifConfig.Flag.debugger()thenJ.Debugger_statementelseJ.Empty_statementin(int0,const_p,queue),[ins,loc]|Prim(p,l)->letres=matchp,lwith|Vectlength,[x]->let(px,cx),queue=access_queue'~ctxqueuexinMlvalue.Array.lengthcx,px,queue|Array_get,[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinMlvalue.Array.fieldcxcy,or_pmutable_p(or_ppxpy),queue|Extern"caml_js_var",[Pc(Stringnm|IStringnm)]|Extern("caml_js_expr"|"caml_pure_js_expr"),[Pc(Stringnm|IStringnm)]->(tryletlexbuf=Lexing.from_stringnminletlexbuf=matchlocwith|J.N|J.U->lexbuf|J.Pipi->((* [pi] is the position of the call, not the
string. We don't have enough information to
recover the start column *)matchpi.srcwith|Somepos_fname->{lexbufwithlex_curr_p={pos_fname;pos_lnum=pi.line;pos_cnum=pi.idx;pos_bol=pi.idx}}|None->lexbuf)inletlex=Parse_js.Lexer.of_lexbuflexbufinlete=Parse_js.parse_exprlexine,const_p,queuewithParse_js.Parsing_errorpi->failwith(Printf.sprintf"Parsing error %S%s at l:%d col:%d"nm(matchpi.Parse_info.srcwith|None->""|Somes->Printf.sprintf", file %S"s)pi.Parse_info.linepi.Parse_info.col))|Extern"%js_array",l->letargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queue'~ctxqueuexincx::args,or_ppropprop',queue)l~init:([],const_p,queue)inJ.EArr(List.mapargs~f:(funx->Somex)),prop,queue|Extern"%closure",[Pc(IStringname|Stringname)]->letprim=Share.get_prim(runtime_functx)namectx.Ctx.shareinprim,const_p,queue|Extern"%caml_js_opt_call",f::o::l->let(pf,cf),queue=access_queue'~ctxqueuefinlet(po,co),queue=access_queue'~ctxqueueoinletargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queue'~ctxqueuexincx::args,or_ppropprop',queue)l~init:([],mutator_p,queue)inecall(J.EDot(cf,"call"))(co::args)loc,or_p(or_ppfpo)prop,queue|Extern"%caml_js_opt_fun_call",f::l->let(pf,cf),queue=access_queue'~ctxqueuefinletargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queue'~ctxqueuexincx::args,or_ppropprop',queue)l~init:([],mutator_p,queue)inecallcfargsloc,or_ppfprop,queue|Extern"%caml_js_opt_meth_call",o::Pc(Stringm|IStringm)::l->let(po,co),queue=access_queue'~ctxqueueoinletargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queue'~ctxqueuexincx::args,or_ppropprop',queue)l~init:([],mutator_p,queue)inecall(J.EDot(co,m))argsloc,or_ppoprop,queue|Extern"%caml_js_opt_new",c::l->let(pc,cc),queue=access_queue'~ctxqueuecinletargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queue'~ctxqueuexin(cx,`Not_spread)::args,or_ppropprop',queue)l~init:([],mutator_p,queue)in(J.ENew(cc,ifList.is_emptyargsthenNoneelseSomeargs),or_ppcprop,queue)|Extern"caml_js_get",[Pvo;Pc(Stringf|IStringf)]whenJ.is_identf->let(po,co),queue=access_queuequeueoinJ.EDot(co,f),or_ppomutable_p,queue|Extern"caml_js_set",[Pvo;Pc(Stringf|IStringf);v]whenJ.is_identf->let(po,co),queue=access_queuequeueoinlet(pv,cv),queue=access_queue'~ctxqueuevinJ.EBin(J.Eq,J.EDot(co,f),cv),or_p(or_ppopv)mutator_p,queue|Extern"caml_js_delete",[Pvo;Pc(Stringf|IStringf)]whenJ.is_identf->let(po,co),queue=access_queuequeueoinJ.EUn(J.Delete,J.EDot(co,f)),or_ppomutator_p,queue|Extern"%overrideMod",[Pc(Stringm|IStringm);Pc(Stringf|IStringf)]->runtime_functx(Printf.sprintf"caml_%s_%s"mf),const_p,queue|Extern"%overrideMod",_->assertfalse|Extern"%caml_js_opt_object",fields->letrecbuild_fieldsqueuel=matchlwith|[]->const_p,[],queue|Pc(Stringnm|IStringnm)::x::r->let(prop,cx),queue=access_queue'~ctxqueuexinletprop',r',queue=build_fieldsqueuerinor_ppropprop',(J.PNSnm,cx)::r',queue|_->assertfalseinletprop,fields,queue=build_fieldsqueuefieldsinJ.EObjfields,prop,queue|Extern"caml_alloc_dummy_function",[_;size]->leti,queue=let(_px,cx),queue=access_queue'~ctxqueuesizeinmatchcxwith|J.ENumi->Int32.to_int(J.Num.to_int32i),queue|_->assertfalseinletargs=Array.to_list(Array.initi~f:(fun_->J.V(Var.fresh())))inletf=J.V(Var.fresh())inletcall=ecall(J.EDot(J.EVarf,"fun"))(List.mapargs~f:(funv->J.EVarv))locinlete=J.EFun(Somef,args,[J.Statement(J.Return_statement(Somecall)),J.N],J.N)ine,const_p,queue|Extern"caml_alloc_dummy_function",_->assertfalse|Externname,l->(letname=Primitive.resolvenameinmatchinternal_primnamewith|Somef->flqueuectxloc|None->ifString.is_prefixname~prefix:"%"thenfailwith(Printf.sprintf"Unresolved internal primitive: %s"name);letprim=Share.get_prim(runtime_functx)namectx.Ctx.shareinletprim_kind=kind(Primitive.kindname)inletargs,prop,queue=List.fold_right~f:(funx(args,prop,queue)->let(prop',cx),queue=access_queue'~ctxqueuexincx::args,or_ppropprop',queue)l~init:([],prim_kind,queue)inecallprimargsloc,prop,queue)|Not,[x]->let(px,cx),queue=access_queue'~ctxqueuexinJ.EBin(J.Minus,one,cx),px,queue|Lt,[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinbool(J.EBin(J.Lt,cx,cy)),or_ppxpy,queue|Le,[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinbool(J.EBin(J.Le,cx,cy)),or_ppxpy,queue|Eq,[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinbool(J.EBin(J.EqEqEq,cx,cy)),or_ppxpy,queue|Neq,[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinbool(J.EBin(J.NotEqEq,cx,cy)),or_ppxpy,queue|IsInt,[x]->let(px,cx),queue=access_queue'~ctxqueuexinbool(Mlvalue.is_immediatecx),px,queue|Ult,[x;y]->let(px,cx),queue=access_queue'~ctxqueuexinlet(py,cy),queue=access_queue'~ctxqueueyinbool(J.EBin(J.Lt,unsignedcx,unsignedcy)),or_ppxpy,queue|(Vectlength|Array_get|Not|IsInt|Eq|Neq|Lt|Le|Ult),_->assertfalseinres,[]andtranslate_instrctxexpr_queuelocinstr=matchinstrwith|Let(x,e)->(let(ce,prop,expr_queue),instrs=translate_exprctxexpr_queuelocxe0inletkeep_namex=matchCode.Var.get_namexwith|None->false|Somes->not(String.is_prefixs~prefix:"jsoo_")inmatchctx.Ctx.live.(Var.idxx),ewith|0,_->(* deadcode is off *)flush_queueexpr_queueprop(instrs@[J.Expression_statementce,loc])|1,_whenConfig.Flag.compact()&&((not(Config.Flag.pretty()))||not(keep_namex))->enqueueexpr_queuepropxceloc1instrs(* We could inline more.
size_v : length of the variable after serialization
size_c : length of the constant after serialization
num : number of occurrence
size_c * n < size_v * n + size_v + 1 + size_c
*)|n,Constant(Int_|Float_)->enqueueexpr_queuepropxcelocninstrs|_->flush_queueexpr_queueprop(instrs@[J.Variable_statement[J.Vx,Some(ce,loc)],loc]))|Set_field(x,n,y)->let(_px,cx),expr_queue=access_queueexpr_queuexinlet(_py,cy),expr_queue=access_queueexpr_queueyinflush_queueexpr_queuemutator_p[J.Expression_statement(J.EBin(J.Eq,Mlvalue.Block.fieldcxn,cy)),loc]|Offset_ref(x,1)->(* FIX: may overflow.. *)let(_px,cx),expr_queue=access_queueexpr_queuexinflush_queueexpr_queuemutator_p[J.Expression_statement(J.EUn(J.IncrA,Mlvalue.Block.fieldcx0)),loc]|Offset_ref(x,n)->(* FIX: may overflow.. *)let(_px,cx),expr_queue=access_queueexpr_queuexinflush_queueexpr_queuemutator_p[J.Expression_statement(J.EBin(J.PlusEq,Mlvalue.Block.fieldcx0,intn)),loc]|Array_set(x,y,z)->let(_px,cx),expr_queue=access_queueexpr_queuexinlet(_py,cy),expr_queue=access_queueexpr_queueyinlet(_pz,cz),expr_queue=access_queueexpr_queuezinflush_queueexpr_queuemutator_p[J.Expression_statement(J.EBin(J.Eq,Mlvalue.Array.fieldcxcy,cz)),loc]andtranslate_instrsctxexpr_queuelocinstr=matchinstrwith|[]->[],expr_queue|instr::rem->letst,expr_queue=translate_instrctxexpr_queuelocinstrinletinstrs,expr_queue=translate_instrsctxexpr_queuelocreminst@instrs,expr_queueandcompile_blockstqueue(pc:Addr.t)frontierinterm=if(not(List.is_emptyqueue))&&(Addr.Set.mempcst.loops||not(Config.Flag.inline()))thenflush_allqueue(compile_blockst[]pcfrontierinterm)else(ifpc>=0then(ifAddr.Set.mempcst.visited_blocksthen(Format.eprintf"Trying to compile a block twice !!!! %d@."pc;assertfalse);st.visited_blocks<-Addr.Set.addpcst.visited_blocks);ifdebug()then(ifAddr.Set.mempcst.loopsthenFormat.eprintf"@[<2>for(;;){@,";Format.eprintf"block %d;@ @?"pc);(ifAddr.Set.mempcst.loopsthenletlab=matchst.loop_stackwith|(_,(l,_))::_->J.Label.succl|[]->J.Label.zeroinst.loop_stack<-(pc,(lab,reffalse))::st.loop_stack);letsuccs=Hashtbl.findst.succspcinletbacks=Hashtbl.findst.backspcin(* Remove limit *)ifpc<0thenList.itersuccs~f:(funpc->unprotect_predsstpc);letsuccs=List.mapsuccs~f:(funpc->pc,dominance_frontierstpc)inletgrey=List.fold_right~f:(fun(_,frontier)grey->Addr.Set.unionfrontiergrey)succs~init:Addr.Set.emptyinletnew_frontier=resolve_nodesintermgreyinletblock=Addr.Map.findpcst.blocksinletseq,queue=translate_instrsst.ctxqueue(source_locationst.ctxpc)block.bodyinletbody=seq@matchblock.branchwith|Code.Pushtrap((pc1,args1),x,(pc2,args2),pc3s)->(* FIX: document this *)letpc2s=resolve_nodesinterm(dominance_frontierstpc2)inletpc3s=Addr.Set.fold(funpc3acc->(* We need to make sure that pc3 is live (indeed, the
continuation may have been optimized away by inlining) *)ifHashtbl.memst.succspc3then(* no need to limit body for simple flow with no instruction.
eg return and branch *)letreclimitpc=ifAddr.Set.mempcpc2sthenfalseelseletblock=Addr.Map.findpcst.blocksin(not(List.is_emptyblock.body))||matchblock.branchwith|Return_->false|Poptrap((pc',_),_)|Branch(pc',_)->limitpc'|_->trueiniflimitpc3thenAddr.Set.addpc3accelseaccelseacc)pc3sAddr.Set.emptyinletgrey=Addr.Set.unionpc2spc3sinAddr.Set.iter(incr_predsst)grey;letprefix,grey',new_interm=colapse_frontierstgreyinterminassert(Addr.Set.cardinalgrey'<=1);letinner_frontier=Addr.Set.unionnew_frontiergrey'inifdebug()thenFormat.eprintf"@[<2>try {@,";letbody=prefix@compile_branchst[](pc1,args1)NoneAddr.Set.emptyinner_frontiernew_interminifdebug()thenFormat.eprintf"} catch {@,";letx=letblock2=Addr.Map.findpc2st.blocksinletm=Subst.build_mappingargs2block2.paramsintryVar.Map.findxmwithNot_found->xinlethandler=compile_blockst[]pc2inner_frontiernew_interminifdebug()thenFormat.eprintf"}@]@ ";Addr.Set.iter(decr_predsst)grey;letafter,exn_escape=ifnot(Addr.Set.is_emptygrey')thenletpc=Addr.Set.choosegrey'inletexn_escape=letx'=Var.forkxinletfound=reffalseinletmap_vary=ifCode.Var.equalxythen(found:=true;x')elseyinletsubst_blockpcblocks=Addr.Map.addpc(Subst.blockmap_var(Addr.Map.findpcblocks))blocksinletblocks=Code.traverse{fold=Code.fold_children}subst_blockpcst.blocksst.blocksinif!foundthenst.blocks<-blocks;if!foundthenSomex'elseNoneinifAddr.Set.mempcfrontierthen[],exn_escapeelsecompile_blockst[]pcfrontierinterm,exn_escapeelse[],Noneinlethandler=ifst.ctx.Ctx.live.(Var.idxx)>0&&Config.Flag.excwrap()then(J.Expression_statement(J.EBin(J.Eq,J.EVar(J.Vx),ecall(Share.get_prim(runtime_funst.ctx)"caml_wrap_exception"st.ctx.Ctx.share)[J.EVar(J.Vx)]J.N)),J.N)::handlerelsehandlerinlethandler=matchexn_escapewith|Somex'->handler@[J.Variable_statement[J.Vx',Some(EVar(J.Vx),J.N)],J.N]|None->handlerinflush_allqueue((J.Try_statement(body,Some(J.Vx,handler),None),source_locationst.ctxpc)::after)|_->letprefix,new_frontier,new_interm=colapse_frontierstnew_frontierinterminassert(Addr.Set.cardinalnew_frontier<=1);(* Beware evaluation order! *)letcond=compile_conditionalstqueuepcblock.branchblock.handlerbacksnew_frontiernew_intermsuccsinprefix@cond@ifAddr.Set.cardinalnew_frontier=0then[]elseletpc=Addr.Set.choosenew_frontierinifAddr.Set.mempcfrontierthen[]elsecompile_blockst[]pcfrontierinterminifAddr.Set.mempcst.loopsthenletlabel=matchst.loop_stackwith|(_,(l,used))::r->st.loop_stack<-r;if!usedthenSomelelseNone|[]->assertfalseinletst=(J.For_statement(J.LeftNone,None,None,Js_simpl.block(ifAddr.Set.cardinalfrontier>0then(ifdebug()thenFormat.eprintf"@ break (%d); }@]"(Addr.Set.choosenew_frontier);body@[J.Break_statementNone,J.N])else(ifdebug()thenFormat.eprintf"}@]";body))),source_locationst.ctxpc)inmatchlabelwith|None->[st]|Somelabel->[J.Labelled_statement(label,st),J.N]elsebody)andcolapse_frontierstnew_frontierinterm=ifAddr.Set.cardinalnew_frontier>1then(ifdebug()thenFormat.eprintf"colapse frontier into %d: %s@."st.interm_idx(string_of_setnew_frontier);letx=Code.Var.fresh_n"switch"inleta=Addr.Set.elementsnew_frontier|>List.map~f:(funpc->pc,get_predsstpc)|>List.sort~cmp:(fun(_,(c1:int))(_,(c2:int))->comparec2c1)|>List.map~f:fstinifdebug()thenFormat.eprintf"@ var %a;"Code.Var.printx;letidx=st.interm_idxinst.interm_idx<-idx-1;letswitch=letcases=Array.of_list(List.mapa~f:(funpc->pc,[]))inifArray.lengthcases>2thenCode.Switch(x,cases,[||])elseCode.Cond(x,cases.(1),cases.(0))inst.blocks<-Addr.Map.addidx{params=[];handler=None;body=[];branch=switch}st.blocks;letpc_i=List.mapi~f:(funipc->pc,i)ainletdefault=0in(* There is a branch from this switch to the members
of the frontier. *)Addr.Set.iter(funpc->incr_predsstpc)new_frontier;(* Put a limit: we are going to remove other branches
to the members of the frontier (in compile_conditional),
but they should remain in the frontier. *)Addr.Set.iter(funpc->protect_predsstpc)new_frontier;Hashtbl.addst.succsidx(Addr.Set.elementsnew_frontier);Hashtbl.addst.backsidxAddr.Set.empty;([J.Variable_statement[J.Vx,Some(intdefault,J.N)],J.N],Addr.Set.singletonidx,List.fold_rightpc_i~init:interm~f:(fun(pc,i)interm->Addr.Map.addpc(idx,(x,i,default=i))interm)))else[],new_frontier,intermandcompile_decision_treest_queuehandlerbacksfrontierintermsuccsloccxdtree=(* Some changes here may require corresponding changes
in function [DTree.fold_cont] above. *)letrecloopcx=function|DTree.Empty->assertfalse|DTree.Branch((pc,_)ascont)->(* Block of code that never continues (either returns, throws an exception
or loops back) *)(* If not found in successors, this is a backward edge *)letnever=letd=tryList.assocpcsuccswithNot_found->Addr.Set.emptyin(not(Addr.Set.mempcfrontier||Addr.Map.mempcinterm))&&Addr.Set.is_emptydinnever,compile_branchst[]conthandlerbacksfrontierinterm|DTree.If(cond,cont1,cont2)->letnever1,iftrue=loopcxcont1inletnever2,iffalse=loopcxcont2inlete'=matchcondwith|IsTrue->cx|CEqn->J.EBin(J.EqEqEq,int32n,cx)|CLtn->J.EBin(J.Lt,int32n,cx)|CLen->J.EBin(J.Le,int32n,cx)in(never1&&never2,Js_simpl.if_statemente'loc(Js_simpl.blockiftrue)never1(Js_simpl.blockiffalse)never2)|DTree.Switcha->letall_never=reftrueinletlen=Array.lengthainletlast_index=len-1inletarr=Array.mapia~f:(funi(ints,cont)->letnever,cont=loopcxcontinifnotneverthenall_never:=false;letcont=ifnever||(* default case *)i=last_indexthencontelsecont@[J.Break_statementNone,J.N]inints,cont)inlet_,last=arr.(last_index)inletl=Array.to_list(Array.subarr~pos:0~len:(len-1))inletl=List.flatten(List.mapl~f:(fun(ints,br)->map_last(funlasti->inti,iflastthenbrelse[])ints))in!all_never,[J.Switch_statement(cx,l,Somelast,[]),loc]inletcx,binds=matchcxwith|(J.EVar_|_)whenDTree.nbcompdtree<=1->cx,[]|_->letv=J.V(Code.Var.fresh())inJ.EVarv,[J.Variable_statement[v,Some(cx,J.N)],J.N]inbinds@snd(loopcxdtree)andcompile_conditionalstqueuepclasthandlerbacksfrontierintermsuccs=List.itersuccs~f:(fun(pc,_)->ifAddr.Map.mempcintermthendecr_predsstpc);(ifdebug()thenmatchlastwith|Branch_|Poptrap_|Pushtrap_->()|Return_->Format.eprintf"ret"|Raise_->Format.eprintf"raise"|Stop->Format.eprintf"stop"|Cond_->Format.eprintf"@[<hv 2>cond{@,"|Switch_->Format.eprintf"@[<hv 2>switch{@,");letloc=source_locationst.ctxpcinletres=matchlastwith|Returnx->let(_px,cx),queue=access_queuequeuexinflush_allqueue[J.Return_statement(Somecx),loc]|Raise(x,k)->let(_px,cx),queue=access_queuequeuexinflush_allqueue(throw_statementst.ctxcxkloc)|Stop->flush_allqueue[J.Return_statementNone,loc]|Branchcont->compile_branchstqueueconthandlerbacksfrontierinterm|Pushtrap_->assertfalse|Poptrap(cont,_)->flush_allqueue(compile_branchst[]contNonebacksfrontierinterm)|Cond(x,c1,c2)->let(_px,cx),queue=access_queuequeuexinletb=compile_decision_treestqueuehandlerbacksfrontierintermsuccsloccx(DTree.build_ifc1c2)inflush_allqueueb|Switch(x,[||],a2)->let(_px,cx),queue=access_queuequeuexinletcode=compile_decision_treestqueuehandlerbacksfrontierintermsuccsloc(Mlvalue.Block.tagcx)(DTree.build_switcha2)inflush_allqueuecode|Switch(x,a1,[||])->let(_px,cx),queue=access_queuequeuexinletcode=compile_decision_treestqueuehandlerbacksfrontierintermsuccsloccx(DTree.build_switcha1)inflush_allqueuecode|Switch(x,a1,a2)->(* The variable x is accessed several times, so we can directly
refer to it *)letb1=compile_decision_treestqueuehandlerbacksfrontierintermsuccsloc(varx)(DTree.build_switcha1)inletb2=compile_decision_treestqueuehandlerbacksfrontierintermsuccsloc(Mlvalue.Block.tag(varx))(DTree.build_switcha2)inletcode=Js_simpl.if_statement(Mlvalue.is_immediate(varx))loc(Js_simpl.blockb1)false(Js_simpl.blockb2)falseinflush_allqueuecodein(ifdebug()thenmatchlastwith|Branch_|Poptrap_|Pushtrap_|Return_|Raise_|Stop->()|Switch_|Cond_->Format.eprintf"}@]@ ");resandcompile_argument_passingctxqueue(pc,args)_backscontinuation=ifList.is_emptyargsthencontinuationqueueelseletblock=Addr.Map.findpcctx.Ctx.blocksinparallel_renamingblock.paramsargscontinuationqueueandcompile_exn_handlingctxqueue(pc,args)handlercontinuation=ifpc<0thencontinuationqueueelseletblock=Addr.Map.findpcctx.Ctx.blocksinmatchblock.handlerwith|None->continuationqueue|Some(x0,(h_pc,h_args))->letold_args=matchhandlerwith|Some(y,(old_pc,old_args))->assert(Var.comparex0y=0&&old_pc=h_pc&&List.lengthold_args=List.lengthh_args);old_args|None->[]in(* When an extra block is inserted during code generation,
args is [] *)letm=Subst.build_mapping(ifList.is_emptyargsthen[]elseblock.params)argsinleth_block=Addr.Map.findh_pcctx.Ctx.blocksinletrecloopcontinuationoldargsparamsqueue=matchargs,paramswith|[],[]->continuationqueue|x::args,y::params->letz,old=matcholdwith|[]->None,[]|z::old->Somez,oldinletx'=trySome(Var.Map.findxm)withNot_found->SomexinifVar.comparexx0=0||Option.equalVar.equalx'zthenloopcontinuationoldargsparamsqueueelselet(px,cx),queue=access_queuequeuexinletst,queue=(*FIX: we should flush only the variables we need rather than doing this;
do the same for closure free variables *)match2(*ctx.Ctx.live.(Var.idx y)*)with|0->assertfalse|1->enqueuequeuepxycx(source_locationctxpc)1[]|_->flush_queuequeuepx[(letloc=source_locationctxpcinJ.Variable_statement[J.Vy,Some(cx,loc)],loc)]inst@loopcontinuationoldargsparamsqueue|_->assertfalseinloopcontinuationold_argsh_argsh_block.paramsqueueandcompile_branchstqueue((pc,_)ascont)handlerbacksfrontierinterm=compile_argument_passingst.ctxqueuecontbacks(funqueue->compile_exn_handlingst.ctxqueueconthandler(funqueue->ifAddr.Set.mempcbacksthen(letlabel=matchst.loop_stackwith|[]->assertfalse|(pc',_)::rem->ifpc=pc'thenNoneelseletlab,used=List.assocpcreminused:=true;Somelabinifdebug()thenifOption.is_nonelabelthenFormat.eprintf"continue;@ "elseFormat.eprintf"continue (%d);@ "pc;flush_allqueue[J.Continue_statementlabel,J.N])elseifAddr.Set.mempcfrontier||Addr.Map.mempcintermthen(ifdebug()thenFormat.eprintf"(br %d)@ "pc;flush_allqueue(compile_branch_selectionpcinterm))elsecompile_blockstqueuepcfrontierinterm))andcompile_branch_selectionpcinterm=tryletpc,(x,i,default)=Addr.Map.findpcinterminifdebug()thenFormat.eprintf"@ %a=%d;"Code.Var.printxi;letbranch=compile_branch_selectionpcinterminifdefaultthenbranchelse(J.Expression_statement(EBin(Eq,EVar(J.Vx),inti)),J.N)::branchwithNot_found->[]andcompile_closurectx(pc,args)=letst={visited_blocks=Addr.Set.empty;loops=Addr.Set.empty;loop_stack=[];succs=Hashtbl.create17;backs=Hashtbl.create17;preds=Hashtbl.create17;interm_idx=-1;ctx;blocks=ctx.Ctx.blocks}inbuild_graphstpcAddr.Set.empty;letcurrent_blocks=st.visited_blocksinst.visited_blocks<-Addr.Set.empty;ifdebug()thenFormat.eprintf"@[<hov 2>closure{@,";letres=compile_branchst[](pc,args)NoneAddr.Set.emptyAddr.Set.emptyAddr.Map.emptyinifAddr.Set.cardinalst.visited_blocks<>Addr.Set.cardinalcurrent_blocksthen(letmissing=Addr.Set.diffcurrent_blocksst.visited_blocksinFormat.eprintf"Some blocks not compiled %s!@."(string_of_setmissing);assertfalse);ifdebug()thenFormat.eprintf"}@]@ ";List.mapres~f:(fun(st,loc)->J.Statementst,loc)letgenerate_shared_valuectx=letstrings=(J.Statement(J.Variable_statement((matchctx.Ctx.exported_runtimewith|None->[]|Somev->[J.Vv,Some(J.EDot(s_varConstant.global_object,"jsoo_runtime"),J.N)])@List.map(StringMap.bindingsctx.Ctx.share.Share.vars.Share.strings)~f:(fun(s,v)->v,Some(str_jss,J.N))@List.map(StringMap.bindingsctx.Ctx.share.Share.vars.Share.prims)~f:(fun(s,v)->v,Some(runtime_functxs,J.N)))),J.U)inifnot(Config.Flag.inline_callgen())thenletapplies=List.map(IntMap.bindingsctx.Ctx.share.Share.vars.Share.applies)~f:(fun(n,v)->matchgenerate_apply_functxnwith|J.EFun(_,param,body,nid)->J.Function_declaration(v,param,body,nid),J.U|_->assertfalse)instrings::applieselse[strings]letcompile_programctxpc=letres=compile_closurectx(pc,[])inletres=generate_shared_valuectx@resinifdebug()thenFormat.eprintf"@.@.";resletf(p:Code.program)~exported_runtime~live_varsdebug=lett'=Timer.make()inletshare=Share.get~alias_prims:exported_runtimepinletexported_runtime=ifexported_runtimethenSome(Code.Var.fresh_n"runtime")elseNoneinletctx=Ctx.initial~exported_runtimep.blockslive_varssharedebuginletp=compile_programctxp.startiniftimes()thenFormat.eprintf" code gen.: %a@."Timer.printt';p