123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705(* Js_of_ocaml compiler
* http://www.ocsigen.org/js_of_ocaml/
*
* 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.
*)modulePoly=structexternal(<):'a->'a->bool="%lessthan"external(<=):'a->'a->bool="%lessequal"external(<>):'a->'a->bool="%notequal"external(=):'a->'a->bool="%equal"external(>):'a->'a->bool="%greaterthan"external(>=):'a->'a->bool="%greaterequal"externalcompare:'a->'a->int="%compare"externalequal:'a->'a->bool="%equal"endmoduleInt_replace_polymorphic_compare=structlet(<)(x:int)y=x<ylet(<=)(x:int)y=x<=ylet(<>)(x:int)y=x<>ylet(=)(x:int)y=x=ylet(>)(x:int)y=x>ylet(>=)(x:int)y=x>=yletcompare(x:int)y=comparexyletequal(x:int)y=x=yletmax(x:int)y=ifx>=ythenxelseyletmin(x:int)y=ifx<=ythenxelseyendincludeInt_replace_polymorphic_compareletquiet=reffalseletwarnfmt=Format.ksprintf(funs->ifnot!quietthenFormat.eprintf"%s%!"s)fmtletfail=reftrueletfailwith_fmt=Printf.ksprintf(funs->if!failthenfailwithselseFormat.eprintf"%s@."s)fmtletraise_exn=if!failthenraiseexnelseFormat.eprintf"%s@."(Printexc.to_stringexn)letint_num_bits=letsize=ref0inleti=ref(-1)inwhile!i<>0doi:=!ilsl1;incrsizedone;!sizemoduleList=structincludeListLabelsletfilter_map~fl=letl=List.fold_left(funaccx->matchfxwith|Somex->x::acc|None->acc)[]linrevlletslow_mapl~f=rev(rev_map~fl)letmax_non_tailcall=matchSys.backend_typewith|Sys.Native|Sys.Bytecode->1_000|Sys.Other_->50letreccount_map~flctr=matchlwith|[]->[]|[x1]->letf1=fx1in[f1]|[x1;x2]->letf1=fx1inletf2=fx2in[f1;f2]|[x1;x2;x3]->letf1=fx1inletf2=fx2inletf3=fx3in[f1;f2;f3]|[x1;x2;x3;x4]->letf1=fx1inletf2=fx2inletf3=fx3inletf4=fx4in[f1;f2;f3;f4]|x1::x2::x3::x4::x5::tl->letf1=fx1inletf2=fx2inletf3=fx3inletf4=fx4inletf5=fx5inf1::f2::f3::f4::f5::(ifctr>max_non_tailcallthenslow_map~ftlelsecount_map~ftl(ctr+1))letmapl~f=count_map~fl0letrectake'accnl=ifn=0thenacc,lelsematchlwith|[]->acc,[]|x::xs->take'(x::acc)(predn)xslettakenl=letx,xs=take'[]nlinrevx,xsletreclast=function|[]->None|[x]->Somex|_::xs->lastxsletsort_uniq~comparel=letl=List.sortcomparelinmatchlwith|([]|[_])asl->l|x::xs->letrecloopprev=function|[]->[prev]|x::restwhencomparexprev=0->loopprevrest|x::rest->prev::loopxrestinloopxxsletis_empty=function|[]->true|_->falseletpartition_mapt~f=letreclooptfstsnd=matchtwith|[]->revfst,revsnd|x::t->(matchfxwith|`Fsty->loopt(y::fst)snd|`Sndy->looptfst(y::snd))inloopt[][]lettail_appendl1l2=rev_append(revl1)l2letreccount_appendl1l2count=matchl2with|[]->l1|_->(matchl1with|[]->l2|[x1]->x1::l2|[x1;x2]->x1::x2::l2|[x1;x2;x3]->x1::x2::x3::l2|[x1;x2;x3;x4]->x1::x2::x3::x4::l2|x1::x2::x3::x4::x5::tl->x1::x2::x3::x4::x5::(ifcount>max_non_tailcallthentail_appendtll2elsecount_appendtll2(count+1)))letappendl1l2=count_appendl1l20letgroupl~f=letrecloop(l:'alist)(this_group:'alist)(acc:'alistlist):'alistlist=matchlwith|[]->List.rev(List.revthis_group::acc)|x::xs->letpred=List.hdthis_groupiniffxpredthenloopxs(x::this_group)accelseloopxs[x](List.revthis_group::acc)inmatchlwith|[]->[]|x::xs->loopxs[x][]letconcat_map~fl=letrecauxfacc=function|[]->revacc|x::l->letxs=fxinauxf(rev_appendxsacc)linauxf[]lendlet(@)=List.appendmoduleNativeint=structincludeNativeintexternalequal:nativeint->nativeint->bool="%equal"endmoduleInt32=structincludeInt32external(<):int32->int32->bool="%lessthan"external(<=):int32->int32->bool="%lessequal"external(<>):int32->int32->bool="%notequal"external(=):int32->int32->bool="%equal"external(>):int32->int32->bool="%greaterthan"external(>=):int32->int32->bool="%greaterequal"externalcompare:int32->int32->int="%compare"externalequal:int32->int32->bool="%equal"letwarn_overflow~to_dec~to_hexii32=warn"Warning: integer overflow: integer 0x%s (%s) truncated to 0x%lx (%ld); the \
generated code might be incorrect.@."(to_hexi)(to_deci)i32i32letconvert_warning_on_overflow~to_int32~of_int32~equal~to_dec~to_hexx=leti32=to_int32xinletx'=of_int32i32inifnot(equalx'x)thenwarn_overflow~to_dec~to_hexxi32;i32letof_int_warning_on_overflowi=convert_warning_on_overflow~to_int32:Int32.of_int~of_int32:Int32.to_int~equal:Int_replace_polymorphic_compare.(=)~to_dec:(Printf.sprintf"%d")~to_hex:(Printf.sprintf"%x")iletof_nativeint_warning_on_overflown=convert_warning_on_overflow~to_int32:Nativeint.to_int32~of_int32:Nativeint.of_int32~equal:Nativeint.equal~to_dec:(Printf.sprintf"%nd")~to_hex:(Printf.sprintf"%nx")nendmoduleOption=structletmap~fx=matchxwith|None->None|Somev->Some(fv)letbind~fx=matchxwith|None->None|Somev->fvletiter~fx=matchxwith|None->()|Somev->fvletfilter~fx=matchxwith|None->None|Somev->iffvthenSomevelseNoneletcomparecompare_eltab=matcha,bwith|None,None->0|None,Some_->-1|Some_,None->1|Somea,Someb->compare_eltabletequalequal_eltab=matcha,bwith|None,None->true|Somea,Someb->equal_eltab|Some_,None|None,Some_->falseletis_none=function|None->true|Some_->falseletis_some=function|None->false|Some_->trueletvalue~default=function|None->default|Somes->sendmoduleInt64=structincludeInt64letequal(a:int64)(b:int64)=Poly.(=)abendmoduleFloat=structtypet=floatletequal(a:float)(b:float)=Int64.equal(Int64.bits_of_floata)(Int64.bits_of_floatb)(* Re-defined here to stay compatible with OCaml 4.02 *)externalclassify_float:float->fpclass="caml_classify_float"external(<):t->t->bool="%lessthan"external(<=):t->t->bool="%lessequal"external(<>):t->t->bool="%notequal"external(=):t->t->bool="%equal"external(>):t->t->bool="%greaterthan"external(>=):t->t->bool="%greaterequal"endmoduleBool=structexternal(<>):bool->bool->bool="%notequal"external(=):bool->bool->bool="%equal"external(>):bool->bool->bool="%greaterthan"externalequal:bool->bool->bool="%equal"endmoduleChar=structincludeCharexternal(<):char->char->bool="%lessthan"external(<=):char->char->bool="%lessequal"external(<>):char->char->bool="%notequal"external(=):char->char->bool="%equal"external(>):char->char->bool="%greaterthan"external(>=):char->char->bool="%greaterequal"externalcompare:char->char->int="%compare"externalequal:char->char->bool="%equal"letis_alpha=function|'a'..'z'|'A'..'Z'->true|_->falseletis_num=function|'0'..'9'->true|_->falseletlowercase_asciic=matchcwith|'A'..'Z'asc->Char.unsafe_chr(Char.codec+32)|_->cletuppercase_asciic=matchcwith|'a'..'z'asc->Char.unsafe_chr(Char.codec-32)|_->cendmoduleBytes=structincludeBytesLabelsletsub_stringb~pos:ofs~len=unsafe_to_string(Bytes.subbofslen)endmoduleString=structincludeStringLabelsletequal(a:string)(b:string)=Poly.(a=b)lethash(a:string)=Hashtbl.hashaletis_empty=function|""->true|_->falseletis_prefix~prefixs=letlen_a=lengthprefixinletlen_s=lengthsiniflen_a>len_sthenfalseelseletmax_idx_a=len_a-1inletrecloopi=ifi>max_idx_athentrueelseifnot(Char.equal(unsafe_getprefixi)(unsafe_getsi))thenfalseelseloop(i+1)inloop0letdrop_prefix~prefixs=letplen=String.lengthprefixinifplen>String.lengthsthenNoneelsetryfori=0toString.lengthprefix-1doifnot(Char.equals.[i]prefix.[i])thenraiseExitdone;Some(String.subsplen(String.lengths-plen))withExit->Noneletfor_all=letrecloops~f~lasti=ifi>lastthentrueelseiff(String.unsafe_getsi)thenloops~f~last(i+1)elsefalseinfuns~f->loops~f~last:(String.lengths-1)0letis_asciis=letres=reftrueinfori=0toString.lengths-1domatchs.[i]with|'\000'..'\127'->()|'\128'..'\255'->res:=falsedone;!reslethas_backslashs=letres=reffalseinfori=0toString.lengths-1doifChar.equals.[i]'\\'thenres:=truedone;!resletsplit_char~sepp=String.split_on_charsepp(* copied from https://github.com/ocaml/ocaml/pull/10 *)letsplit~seps=letsep_len=String.lengthsepinifsep_len=1thensplit_char~sep:sep.[0]selseletsep_max=sep_len-1inifsep_max<0theninvalid_arg"String.split: empty separator"elselets_max=String.lengths-1inifs_max<0then[""]elseletacc=ref[]inletsub_start=ref0inletk=ref0inleti=ref0in(* We build the substrings by running from the start of [s] to the
end with [i] trying to match the first character of [sep] in
[s]. If this matches, we verify that the whole [sep] is matched
using [k]. If this matches we extract a substring from the start
of the current substring [sub_start] to [!i - 1] (the position
before the [sep] we found). We then continue to try to match
with [i] by starting after the [sep] we just found, this is also
becomes the start position of the next substring. If [i] is such
that no separator can be found we exit the loop and make a
substring from [sub_start] until the end of the string. *)while!i+sep_max<=s_maxdoifnot(Char.equal(String.unsafe_gets!i)(String.unsafe_getsep0))thenincrielse((* Check remaining [sep] chars match, access to unsafe s (!i + !k) is
guaranteed by loop invariant. *)k:=1;while!k<=sep_max&&Char.equal(String.unsafe_gets(!i+!k))(String.unsafe_getsep!k)doincrkdone;if!k<=sep_maxthen(* no match *)incrielseletnew_sub_start=!i+sep_max+1inletsub_end=!i-1inletsub_len=sub_end-!sub_start+1inacc:=String.subs!sub_startsub_len::!acc;sub_start:=new_sub_start;i:=new_sub_start)done;List.rev(String.subs!sub_start(s_max-!sub_start+1)::!acc)letapply1f(s:string):string=letb=Bytes.of_stringsinifBytes.lengthb=0thenselse(Bytes.unsafe_setb0(f(Bytes.unsafe_getb0));Bytes.to_stringb)letlsplit2line~on:delim=tryletpos=indexlinedeliminSome(subline~pos:0~len:pos,subline~pos:(pos+1)~len:(lengthline-pos-1))withNot_found->Noneletcapitalize_asciis=apply1Char.uppercase_asciisletuncapitalize_asciis=apply1Char.lowercase_asciisendmoduleInt=structtypet=intletcompare(x:int)y=comparexyletequal(x:t)y=x=ylethash(x:t)=Hashtbl.hashxendmoduleIntSet=Set.Make(Int)moduleIntMap=Map.Make(Int)moduleStringSet=Set.Make(String)moduleStringMap=Map.Make(String)moduleBitSet:sigtypetvalcreate:unit->tvalmem:t->int->boolvalset:t->int->unitvalunset:t->int->unitvalcopy:t->tvaliter:f:(int->unit)->t->unitvalsize:t->intvalnext_free:t->int->intvalnext_mem:t->int->intend=structtypet={mutablearr:intarray}letcreate()={arr=Array.make10}letsizet=Array.lengtht.arr*int_num_bitsletmemti=letarr=t.arrinletidx=i/int_num_bitsinletoff=imodint_num_bitsinidx<Array.lengtharr&&Array.unsafe_getarridxland(1lsloff)<>0letsetti=letidx=i/int_num_bitsinletoff=imodint_num_bitsinletsize=ref(Array.lengtht.arr)inwhileidx>=!sizedosize:=!size*2done;if!size<>Array.lengtht.arrthen(leta=Array.make!size0inArray.blitt.arr0a0(Array.lengtht.arr);t.arr<-a);Array.unsafe_sett.arridx(Array.unsafe_gett.arridxlor(1lsloff))letunsetti=letidx=i/int_num_bitsinletoff=imodint_num_bitsinletsize=Array.lengtht.arrinifidx>=sizethen()elseifArray.unsafe_gett.arridxland(1lsloff)<>0thenArray.unsafe_sett.arridx(Array.unsafe_gett.arridxlxor(1lsloff))letnext_freeti=letx=refiinwhilememt!xdoincrxdone;!xletnext_memti=letx=refiinwhilenot(memt!x)doincrxdone;!xletcopyt={arr=Array.copyt.arr}letiter~ft=fori=0tosizetdoifmemtithenfidoneendmoduleArray=structincludeArrayLabelsletfold_right_ia~f~init:x=letr=refxinfori=Array.lengtha-1downto0dor:=fi(Array.unsafe_getai)!rdone;!rletequaleqab=letlen_a=Array.lengthainiflen_a<>Array.lengthbthenfalseelseleti=ref0inwhile!i<len_a&&eqa.(!i)b.(!i)doincridone;!i=len_aendmoduleFilename=structincludeFilenamelettemp_file_name=(* Inlined unavailable Filename.temp_file_name. Filename.temp_file gives
us incorrect permissions. https://github.com/ocsigen/js_of_ocaml/issues/182 *)letprng=lazy(Random.State.make_self_init())infun~temp_dirprefixsuffix->letrnd=Random.State.bits(Lazy.forceprng)land0xFFFFFFinFilename.concattemp_dir(Printf.sprintf"%s%06x%s"prefixrndsuffix)letgen_filefilef=letf_tmp=temp_file_name~temp_dir:(Filename.dirnamefile)(Filename.basenamefile)".tmp"intryletch=open_out_binf_tmpin(tryfchwithe->close_outch;raisee);close_outch;(trySys.removefilewithSys_error_->());Sys.renamef_tmpfilewithexc->Sys.removef_tmp;raiseexcend