123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338(* Yoann Padioleau
*
* Copyright (C) 1998-2013 Yoann Padioleau
*
* This library is free software; you can redistribute it and/or
* modify it under the terms of the GNU Lesser General Public License
* version 2.1 as published by the Free Software Foundation, with the
* special exception on linking described in file license.txt.
*
* This library is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the file
* license.txt for more details.
*)(*###########################################################################*)(* Prelude *)(*###########################################################################*)(*****************************************************************************)(* Prelude *)(*****************************************************************************)(* The following functions should be in their respective sections but
* because some functions in some sections use functions in other
* sections, and because I don't want to take care of the order of
* those sections, of those dependencies, I put the functions causing
* dependency problem here. C is better than OCaml on this with the
* ability to declare prototypes, enabling some form of forward
* reference.
*)letspf=Printf.sprintfexceptionTimeoutexceptionUnixExitofintletrecdropnxs=match(n,xs)with|(0,_)->xs|(_,[])->failwith"drop: not enough"|(n,x::xs)->drop(n-1)xslettakenxs=letrecnextnxsacc=match(n,xs)with|(0,_)->List.revacc|(_,[])->failwith"Common.take: not enough"|(n,x::xs)->next(n-1)xs(x::acc)innextnxs[]letrecenum_origxn=ifx=nthen[n]elsex::enum_orig(x+1)nletenumxn=ifnot(x<=n)thenfailwith(Printf.sprintf"bad values in enum, expect %d <= %d"xn);letrecenum_auxaccxn=ifx=nthenn::accelseenum_aux(x::acc)(x+1)ninList.rev(enum_aux[]xn)letpushvl=l:=v::!lletdebugger=reffalseletunwind_protectfcleanup=if!debuggerthenf()elsetryf()withe->begincleanupe;raiseeendletfinalizefcleanup=(* bug: we can not just call f in debugger mode because
* this change the semantic of the program. I originally
* put this code below:
* if !debugger then f () else
* because I wanted some errors to pop-out to the top so I can
* debug them but because now I use save_excursion and finalize
* quite a lot this changes too much the semantic.
* TODO: maybe I should not use save_excursion so much ? maybe
* -debugger helps see code that I should refactor ?
*)tryletres=f()incleanup();reswithe->cleanup();raiseelet(unlines:stringlist->string)=funs->(String.concat"\n"s)^"\n"let(lines:string->stringlist)=funs->letreclines_aux=function|[]->[]|[x]->ifx=""then[]else[x]|x::xs->x::lines_auxxsinStr.split_delim(Str.regexp"\n")s|>lines_auxletsave_excursionreferencenewvf=letold=!referenceinreference:=newv;finalizef(fun_->reference:=old;)letmemoized?(use_cache=true)hkf=ifnotuse_cachethenf()elsetryHashtbl.findhkwithNot_found->letv=f()inbeginHashtbl.addhkv;vendexceptionTodoexceptionImpossibleexceptionMulti_found(* to be consistent with Not_found *)letexn_to_sexn=Printexc.to_stringexn(*###########################################################################*)(* Basic features *)(*###########################################################################*)(*****************************************************************************)(* Debugging/logging *)(*****************************************************************************)letprs=print_strings;print_string"\n";flushstdoutletpr2s=prerr_strings;prerr_string"\n";flushstderrletpr_xxxxxxxxxxxxxxxxx()=pr"-----------------------------------------------------------------------"letpr2_xxxxxxxxxxxxxxxxx()=pr2"-----------------------------------------------------------------------"let_already_printed=Hashtbl.create101letdisable_pr2_once=reffalseletxxx_oncefs=if!disable_pr2_oncethenpr2selseifnot(Hashtbl.mem_already_printeds)thenbeginHashtbl.add_already_printedstrue;f("(ONCE) "^s);endletpr2_onces=xxx_oncepr2s(* start of dumper.ml *)(* Dump an OCaml value into a printable string.
* By Richard W.M. Jones (rich@annexia.org).
* dumper.ml 1.2 2005/02/06 12:38:21 rich Exp
*)openPrintfopenObjletrecdump2r=ifis_intrthenstring_of_int(magicr:int)else((* Block. *)letrecget_fieldsacc=function|0->acc|n->letn=n-1inget_fields(fieldrn::acc)ninletrecis_listr=ifis_intrthen(if(magicr:int)=0thentrue(* [] *)elsefalse)else(lets=sizerandt=tagrinift=0&&s=2thenis_list(fieldr1)(* h :: t *)elsefalse)inletrecget_listr=ifis_intrthen[]elseleth=fieldr0andt=get_list(fieldr1)inh::tinletopaquename=(* XXX In future, print the address of value 'r'. Not possible in
* pure OCaml at the moment.
*)"<"^name^">"inlets=sizerandt=tagrin(* From the tag, determine the type of block. *)ifis_listrthen((* List. *)letfields=get_listrin"["^String.concat"; "(List.mapdump2fields)^"]")elseift=0then((* Tuple, array, record. *)letfields=get_fields[]sin"("^String.concat", "(List.mapdump2fields)^")")(* Note that [lazy_tag .. forward_tag] are < no_scan_tag. Not
* clear if very large constructed values could have the same
* tag. XXX *)elseift=lazy_tagthenopaque"lazy"elseift=closure_tagthenopaque"closure"elseift=object_tagthen((* Object. *)letfields=get_fields[]sinletclasz,id,slots=matchfieldswithh::h'::t->h,h',t|_->assertfalsein(* No information on decoding the class (first field). So just print
* out the ID and the slots.
*)"Object #"^dump2id^" ("^String.concat", "(List.mapdump2slots)^")")elseift=infix_tagthenopaque"infix"elseift=forward_tagthenopaque"forward"elseift<no_scan_tagthen((* Constructed value. *)letfields=get_fields[]sin"Tag"^string_of_intt^" ("^String.concat", "(List.mapdump2fields)^")")elseift=string_tagthen("\""^String.escaped(magicr:string)^"\"")elseift=double_tagthen(string_of_float(magicr:float))elseift=abstract_tagthenopaque"abstract"elseift=custom_tagthenopaque"custom"elsefailwith("dump: impossible tag ("^string_of_intt^")"))letdumpv=dump2(reprv)(* end of dumper.ml *)(*
let (dump : 'a -> string) = fun x ->
Dumper.dump x
*)letpr2_genx=pr2(dumpx)(*****************************************************************************)(* Profiling *)(*****************************************************************************)typeprof=ProfAll|ProfNone|ProfSomeofstringlistletprofile=refProfNoneletshow_trace_profile=reffalseletcheck_profilecategory=match!profilewith|ProfAll->true|ProfNone->false|ProfSomel->List.memcategoryllet_profile_table=ref(Hashtbl.create100)letadjust_profile_entrycategorydifftime=let(xtime,xcount)=(tryHashtbl.find!_profile_tablecategorywithNot_found->letxtime=ref0.0inletxcount=ref0inHashtbl.add!_profile_tablecategory(xtime,xcount);(xtime,xcount))inxtime:=!xtime+.difftime;xcount:=!xcount+1;()letprofile_startcategory=failwith"todo"letprofile_endcategory=failwith"todo"(* subtil: don't forget to give all argumens to f, otherwise partial app
* and will profile nothing.
*
* todo: try also detect when complexity augment each time, so can
* detect the situation for a function gets worse and worse ?
*)letprofile_codecategoryf=ifnot(check_profilecategory)thenf()elsebeginif!show_trace_profilethenpr2(spf"> %s"category);lett=Unix.gettimeofday()inletres,prefix=trySome(f()),""withTimeout->None,"*"inletcategory=prefix^categoryin(* add a '*' to indicate timeout func *)lett'=Unix.gettimeofday()inif!show_trace_profilethenpr2(spf"< %s"category);adjust_profile_entrycategory(t'-.t);(matchreswith|Someres->res|None->raiseTimeout);endlet_is_in_exclusif=ref(None:stringoption)letprofile_code_exclusifcategoryf=ifnot(check_profilecategory)thenf()elsebeginmatch!_is_in_exclusifwith|Somes->failwith(spf"profile_code_exclusif: %s but already in %s "categorys);|None->_is_in_exclusif:=(Somecategory);finalize(fun()->profile_codecategoryf)(fun()->_is_in_exclusif:=None)endletprofile_code_inside_exclusif_okcategoryf=failwith"Todo"let(with_open_stringbuf:(((string->unit)*Buffer.t)->unit)->string)=funf->letbuf=Buffer.create1000inletprs=Buffer.add_stringbuf(s^"\n")inf(pr,buf);Buffer.contentsbuf(* todo: also put % ? also add % to see if coherent numbers *)letprofile_diagnostic()=if!profile=ProfNonethen""elseletxs=Hashtbl.fold(funkvacc->(k,v)::acc)!_profile_table[]|>List.sort(fun(k1,(t1,n1))(k2,(t2,n2))->comparet2t1)inwith_open_stringbuf(fun(pr,_)->pr"---------------------";pr"profiling result";pr"---------------------";xs|>List.iter(fun(k,(t,n))->pr(Printf.sprintf"%-40s : %10.3f sec %10d count"k!t!n)))letreport_if_take_timetimethresholdsf=lett=Unix.gettimeofday()inletres=f()inlett'=Unix.gettimeofday()inif(t'-.t>float_of_inttimethreshold)thenpr2(Printf.sprintf"Note: processing took %7.1fs: %s"(t'-.t)s);resletprofile_code2categoryf=profile_codecategory(fun()->if!profile=ProfAllthenpr2("starting: "^category);lett=Unix.gettimeofday()inletres=f()inlett'=Unix.gettimeofday()inif!profile=ProfAllthenpr2(spf"ending: %s, %fs"category(t'-.t));res)(*****************************************************************************)(* Test *)(*****************************************************************************)(* See OUnit *)(*****************************************************************************)(* Persistence *)(*****************************************************************************)letget_valuefilename=letchan=open_infilenameinletx=input_valuechanin(* <=> Marshal.from_channel *)(close_inchan;x)letwrite_valuevalufilename=letchan=open_outfilenamein(output_valuechanvalu;(* <=> Marshal.to_channel *)(* Marshal.to_channel chan valu [Marshal.Closures]; *)close_outchan)(*****************************************************************************)(* Composition/Control *)(*****************************************************************************)(*****************************************************************************)(* Error managment *)(*****************************************************************************)(*****************************************************************************)(* Arguments/options and command line (cocci and acomment) *)(*****************************************************************************)(*
* todo? isn't unison or scott-mcpeak-lib-in-cil handles that kind of
* stuff better ? That is the need to localize command line argument
* while still being able to gathering them. Same for logging.
* Similiar to the type prof = PALL | PNONE | PSOME of string list.
* Same spirit of fine grain config in log4j ?
*
* todo? how mercurial/cvs/git manage command line options ? because they
* all have a kind of DSL around arguments with some common options,
* specific options, conventions, etc.
*
*
* todo? generate the corresponding noxxx options ?
* todo? generate list of options and show their value ?
*
* todo? make it possible to set this value via a config file ?
*
*
*)typearg_spec_full=Arg.key*Arg.spec*Arg.doctypecmdline_options=arg_spec_fulllist(* the format is a list of triples:
* (title of section * (optional) explanation of sections * options)
*)typeoptions_with_title=string*string*arg_spec_fulllisttypecmdline_sections=options_with_titlelist(* ---------------------------------------------------------------------- *)(* now I use argv as I like at the call sites to show that
* this function internally use argv.
*)letparse_optionsoptionsusage_msgargv=letargs=ref[]in(tryArg.parse_argvargvoptions(funfile->args:=file::!args)usage_msg;args:=List.rev!args;!argswith|Arg.Badmsg->Printf.eprintf"%s"msg;exit2|Arg.Helpmsg->Printf.printf"%s"msg;exit0)letusageusage_msgoptions=Arg.usage(Arg.alignoptions)usage_msg(* for coccinelle *)(* If you don't want the -help and --help that are appended by Arg.align *)letarg_align2xs=Arg.alignxs|>List.rev|>drop2|>List.revletshort_usageusage_msg~short_opt=usageusage_msgshort_optletlong_usageusage_msg~short_opt~long_opt=prusage_msg;pr"";letall_options_with_title=(("main options","",short_opt)::long_opt)inall_options_with_title|>List.iter(fun(title,explanations,xs)->prtitle;pr_xxxxxxxxxxxxxxxxx();ifexplanations<>""thenbeginprexplanations;pr""end;arg_align2xs|>List.iter(fun(key,action,s)->pr(" "^key^s));pr"";);()(* copy paste of Arg.parse. Don't want the default -help msg *)letarg_parse2lmsgshort_usage_fun=letargs=ref[]inletf=(funfile->args:=file::!args)inletl=Arg.alignlin(trybeginArg.parse_argvSys.argvlfmsg;args:=List.rev!args;!argsendwith|Arg.Badmsg->(* eprintf "%s" msg; exit 2; *)letxs=linesmsgin(* take only head, it's where the error msg is *)pr2(List.hdxs);short_usage_fun();raise(UnixExit(2))|Arg.Helpmsg->(* printf "%s" msg; exit 0; *)raiseImpossible(* -help is specified in speclist *))(* ---------------------------------------------------------------------- *)typeflag_spec=Arg.key*Arg.spec*Arg.doctypeaction_spec=Arg.key*Arg.doc*action_funcandaction_func=(stringlist->unit)typecmdline_actions=action_speclistexceptionWrongNumberOfArgumentsletoptions_of_actionsaction_refactions=actions|>List.map(fun(key,doc,_func)->(key,(Arg.Unit(fun()->action_ref:=key)),doc))let(action_list:cmdline_actions->Arg.keylist)=funxs->List.map(fun(a,b,c)->a)xslet(do_action:Arg.key->stringlist(* args *)->cmdline_actions->unit)=funkeyargsxs->letassoc=xs|>List.map(fun(a,b,c)->(a,c))inletaction_func=List.assockeyassocinaction_funcargs(* todo? if have a function with default argument ? would like a
* mk_action_0_or_1_arg ?
*)letmk_action_0_argf=(function|[]->f()|_->raiseWrongNumberOfArguments)letmk_action_1_argf=(function|[file]->ffile|_->raiseWrongNumberOfArguments)letmk_action_2_argf=(function|[file1;file2]->ffile1file2|_->raiseWrongNumberOfArguments)letmk_action_3_argf=(function|[file1;file2;file3]->ffile1file2file3|_->raiseWrongNumberOfArguments)letmk_action_4_argf=(function|[file1;file2;file3;file4]->ffile1file2file3file4|_->raiseWrongNumberOfArguments)letmk_action_n_argf=f(*****************************************************************************)(* Equality *)(*****************************************************************************)let(=|=):int->int->bool=(=)let(=<=):char->char->bool=(=)let(=$=):string->string->bool=(=)let(=:=):bool->bool->bool=(=)let(=*=)=(=)(*###########################################################################*)(* Basic types *)(*###########################################################################*)(*****************************************************************************)(* Bool *)(*****************************************************************************)(*****************************************************************************)(* Char *)(*****************************************************************************)(*****************************************************************************)(* Num *)(*****************************************************************************)(*****************************************************************************)(* Tuples *)(*****************************************************************************)(*****************************************************************************)(* Maybe *)(*****************************************************************************)(* type 'a maybe = Just of 'a | None *)let(>>=)m1m2=matchm1with|None->None|Somex->m2x(*
(*http://roscidus.com/blog/blog/2013/10/13/ocaml-tips/#handling-option-types*)
let (|?) maybe default =
match maybe with
| Some v -> v
| None -> Lazy.force default
*)letmap_optf=function|None->None|Somex->Some(fx)letdo_optionf=function|None->()|Somex->fxletopt=do_optionletopt_to_list:'aoption->'alist=function|None->[]|Somex->[x](* not sure why but can't use let (?:) a b = ... then at use time ocaml yells*)let(|||)ab=matchawith|Somex->x|None->btype('a,'b)either=Leftof'a|Rightof'b(* with sexp *)type('a,'b,'c)either3=Left3of'a|Middle3of'b|Right3of'c(* with sexp *)letpartition_eitherfl=letrecpart_eitherleftright=function|[]->(List.revleft,List.revright)|x::l->(matchfxwith|Lefte->part_either(e::left)rightl|Righte->part_eitherleft(e::right)l)inpart_either[][]lletpartition_either3fl=letrecpart_eitherleftmiddleright=function|[]->(List.revleft,List.revmiddle,List.revright)|x::l->(matchfxwith|Left3e->part_either(e::left)middlerightl|Middle3e->part_eitherleft(e::middle)rightl|Right3e->part_eitherleftmiddle(e::right)l)inpart_either[][][]lletrecfilter_some=function|[]->[]|None::l->filter_somel|Somee::l->e::filter_somelletmap_filterfxs=xs|>List.mapf|>filter_someletrecfind_some_optp=function|[]->None|x::l->matchpxwith|Somev->Somev|None->find_some_optplletfind_somepxs=matchfind_some_optpxswith|None->raiseNot_found|Somex->xletrecfind_optfxs=find_some_opt(funx->iffxthenSomexelseNone)xs(*****************************************************************************)(* Regexp, can also use PCRE *)(*****************************************************************************)let(matched:int->string->string)=funis->Str.matched_groupisletmatched1=funs->matched1sletmatched2=funs->(matched1s,matched2s)letmatched3=funs->(matched1s,matched2s,matched3s)letmatched4=funs->(matched1s,matched2s,matched3s,matched4s)letmatched5=funs->(matched1s,matched2s,matched3s,matched4s,matched5s)letmatched6=funs->(matched1s,matched2s,matched3s,matched4s,matched5s,matched6s)letmatched7=funs->(matched1s,matched2s,matched3s,matched4s,matched5s,matched6s,matched7s)let_memo_compiled_regexp=Hashtbl.create101letcandidate_match_funcsre=(* old: Str.string_match (Str.regexp re) s 0 *)letcompile_re=memoized_memo_compiled_regexpre(fun()->Str.regexpre)inStr.string_matchcompile_res0letmatch_funcsre=profile_code"Common.=~"(fun()->candidate_match_funcsre)let(=~)sre=match_funcsreletsplitseps=Str.split(Str.regexpsep)sletjoinsepxs=String.concatsepxs(*****************************************************************************)(* Strings *)(*****************************************************************************)(* ruby *)leti_to_s=string_of_intlets_to_i=int_of_stringletnull_strings=s=$=""(*****************************************************************************)(* Filenames *)(*****************************************************************************)typefilename=string(* TODO could check that exist :) type sux *)(* with sexp *)typedirname=string(* TODO could check that exist :) type sux *)(* with sexp *)(* file or dir *)typepath=stringletchop_dirsymbol=function|swhens=~"\\(.*\\)/$"->matched1s|s->s(* pre: prj_path must not contain regexp symbol *)letfilename_without_leading_pathprj_paths=ifprj_path="/"thenselseletprj_path=chop_dirsymbolprj_pathinifs=$=prj_paththen"."elseifs=~("^"^prj_path^"/\\(.*\\)$")thenmatched1selsefailwith(spf"cant find filename_without_project_path: %s %s"prj_paths)letreadable~roots=filename_without_leading_pathrootsletis_directoryfile=(Unix.statfile).Unix.st_kind=*=Unix.S_DIR(*****************************************************************************)(* Dates *)(*****************************************************************************)(*****************************************************************************)(* Lines/words/strings *)(*****************************************************************************)(*****************************************************************************)(* Process/Files *)(*****************************************************************************)letcommand2s=ignore(Sys.commands)exceptionCmdErrorofUnix.process_status*stringletprocess_output_to_list2?(verbose=false)command=letchan=Unix.open_process_incommandinletres=ref([]:stringlist)inletrecprocess_otl_aux()=lete=input_linechaninres:=e::!res;ifverbosethenpr2e;process_otl_aux()intryprocess_otl_aux()withEnd_of_file->letstat=Unix.close_process_inchanin(List.rev!res,stat)letcmd_to_list?verbosecommand=let(l,exit_status)=process_output_to_list2?verbosecommandinmatchexit_statuswith|Unix.WEXITED0->l|_->raise(CmdError(exit_status,(spf"CMD = %s, RESULT = %s"command(String.concat"\n"l))))letcmd_to_list_and_status=process_output_to_list2(* tail recursive efficient version *)letcatfile=letchan=open_infileinletreccat_auxacc()=(* cant do input_line chan::aux() cos ocaml eval from right to left ! *)let(b,l)=try(true,input_linechan)withEnd_of_file->(false,"")inifbthencat_aux(l::acc)()elseaccincat_aux[]()|>List.rev|>(funx->close_inchan;x)letread_filefile=letic=open_infileinletsize=in_channel_lengthicinletbuf=Bytes.createsizeinreally_inputicbuf0size;close_inic;buf|>Bytes.to_stringletwrite_file~files=letchan=open_outfilein(output_stringchans;close_outchan)(* could be in control section too *)letfilemtimefile=(Unix.statfile).Unix.st_mtime(*
Using an external C functions complicates the linking process of
programs using commons/. Thus, I replaced realpath() with an OCaml-only
similar functions fullpath().
external c_realpath: string -> string option = "caml_realpath"
let realpath2 path =
match c_realpath path with
| Some s -> s
| None -> failwith (spf "problem with realpath on %s" path)
let realpath2 path =
let stat = Unix.stat path in
let dir, suffix =
match stat.Unix.st_kind with
| Unix.S_DIR -> path, ""
| _ -> Filename.dirname path, Filename.basename path
in
let oldpwd = Sys.getcwd () in
Sys.chdir dir;
let realpath_dir = Sys.getcwd () in
Sys.chdir oldpwd;
Filename.concat realpath_dir suffix
let realpath path =
profile_code "Common.realpath" (fun () -> realpath2 path)
*)letfullpathfile=ifnot(Sys.file_existsfile)thenfailwith(spf"fullpath: file (or directory) %s does not exist"file);letdir,base=ifSys.is_directoryfilethenfile,NoneelseFilename.dirnamefile,Some(Filename.basenamefile)in(* save *)letold=Sys.getcwd()inSys.chdirdir;lethere=Sys.getcwd()in(* restore *)Sys.chdirold;matchbasewith|None->here|Somex->Filename.concatherex(* Why a use_cache argument ? because sometimes want disable it but dont
* want put the cache_computation funcall in comment, so just easier to
* pass this extra option.
*)letcache_computation2?(verbose=false)?(use_cache=true)fileext_cachef=ifnotuse_cachethenf()elsebeginifnot(Sys.file_existsfile)thenbeginpr2("WARNING: cache_computation: can't find file "^file);pr2("defaulting to calling the function");f()endelsebeginletfile_cache=(file^ext_cache)inifSys.file_existsfile_cache&&filemtimefile_cache>=filemtimefilethenbeginifverbosethenpr2("using cache: "^file_cache);get_valuefile_cacheendelsebeginletres=f()inwrite_valueresfile_cache;resendendendletcache_computation?verbose?use_cacheabc=profile_code"Common.cache_computation"(fun()->cache_computation2?verbose?use_cacheabc)(* emacs/lisp inspiration (eric cooper and yaron minsky use that too) *)let(with_open_outfile:filename->(((string->unit)*out_channel)->'a)->'a)=funfilef->letchan=open_outfileinletprs=output_stringchansinunwind_protect(fun()->letres=f(pr,chan)inclose_outchan;res)(fune->close_outchan)let(with_open_infile:filename->((in_channel)->'a)->'a)=funfilef->letchan=open_infileinunwind_protect(fun()->letres=fchaninclose_inchan;res)(fune->close_inchan)(* now in prelude:
* exception Timeout
*)(* it seems that the toplevel block such signals, even with this explicit
* command :(
* let _ = Unix.sigprocmask Unix.SIG_UNBLOCK [Sys.sigalrm]
*)(* could be in Control section *)(* subtil: have to make sure that timeout is not intercepted before here, so
* avoid exn handle such as try (...) with _ -> cos timeout will not bubble up
* enough. In such case, add a case before such as
* with Timeout -> raise Timeout | _ -> ...
*
* question: can we have a signal and so exn when in a exn handler ?
*)lettimeout_function?(verbose=false)timeoutval=funf->trybeginSys.set_signalSys.sigalrm(Sys.Signal_handle(fun_->raiseTimeout));ignore(Unix.alarmtimeoutval);letx=f()inignore(Unix.alarm0);xendwithTimeout->beginifverbosethenpr2"timeout (we abort)";raiseTimeout;end|e->(* subtil: important to disable the alarm before relaunching the exn,
* otherwise the alarm is still running.
*
* robust?: and if alarm launched after the log (...) ?
* Maybe signals are disabled when process an exception handler ?
*)beginignore(Unix.alarm0);(* log ("exn while in transaction (we abort too, even if ...) = " ^
Printexc.to_string e);
*)ifverbosethenpr2"exn while in timeout_function";raiseeend(* creation of tmp files, a la gcc *)let_temp_files_created=ref([]:filenamelist)(* ex: new_temp_file "cocci" ".c" will give "/tmp/cocci-3252-434465.c" *)letnew_temp_fileprefixsuffix=letprocessid=i_to_s(Unix.getpid())inlettmp_file=Filename.temp_file(prefix^"-"^processid^"-")suffixinpushtmp_file_temp_files_created;tmp_fileletsave_tmp_files=reffalseleterase_temp_files()=ifnot!save_tmp_filesthenbegin!_temp_files_created|>List.iter(funs->(* pr2 ("erasing: " ^ s); *)command2("rm -f "^s));_temp_files_created:=[]endleterase_this_temp_filef=ifnot!save_tmp_filesthenbegin_temp_files_created:=List.filter(functionx->not(x=$=f))!_temp_files_created;command2("rm -f "^f)end(*###########################################################################*)(* Collection-like types *)(*###########################################################################*)(*****************************************************************************)(* List *)(*****************************************************************************)letexcludepxs=List.filter(funx->not(px))xsletrec(span:('a->bool)->'alist->'alist*'alist)=funp->function|[]->([],[])|x::xs->ifpxthenlet(l1,l2)=spanpxsin(x::l1,l2)else([],x::xs)letrectake_safenxs=match(n,xs)with|(0,_)->[]|(_,[])->[]|(n,x::xs)->x::take_safe(n-1)xsletgroup_byfxs=(* use Hashtbl.find_all property *)leth=Hashtbl.create101in(* could use Set *)lethkeys=Hashtbl.create101inxs|>List.iter(funx->letk=fxinHashtbl.replacehkeysktrue;Hashtbl.addhkx);Hashtbl.fold(funk_acc->(k,Hashtbl.find_allhk)::acc)hkeys[]letgroup_by_multifkeysxs=(* use Hashtbl.find_all property *)leth=Hashtbl.create101in(* could use Set *)lethkeys=Hashtbl.create101inxs|>List.iter(funx->letks=fkeysxinks|>List.iter(funk->Hashtbl.replacehkeysktrue;Hashtbl.addhkx;));Hashtbl.fold(funk_acc->(k,Hashtbl.find_allhk)::acc)hkeys[](* you should really use group_assoc_bykey_eff *)letrecgroup_by_mapped_keyfkeyl=matchlwith|[]->[]|x::xs->letk=fkeyxinlet(xs1,xs2)=List.partition(funx'->letk2=fkeyx'ink=*=k2)xsin(k,(x::xs1))::(group_by_mapped_keyfkeyxs2)letreczipxsys=match(xs,ys)with|([],[])->[]|([],_)->failwith"zip: not same length"|(_,[])->failwith"zip: not same length"|(x::xs,y::ys)->(x,y)::zipxsysletnullxs=matchxswith[]->true|_->falseletindex_listxs=ifnullxsthen[](* enum 0 (-1) generate an exception *)elsezipxs(enum0((List.lengthxs)-1))letindex_list_0xs=index_listxsletindex_list_1xs=xs|>index_list|>List.map(fun(x,i)->x,i+1)letsort_profab=profile_code"Common.sort_by_xxx"(fun()->List.sortab)typeorder=HighFirst|LowFirstletcompare_orderorderab=matchorderwith|HighFirst->compareba|LowFirst->compareabletsort_by_val_highfirstxs=sort_prof(fun(k1,v1)(k2,v2)->comparev2v1)xsletsort_by_val_lowfirstxs=sort_prof(fun(k1,v1)(k2,v2)->comparev1v2)xsletsort_by_key_highfirstxs=sort_prof(fun(k1,v1)(k2,v2)->comparek2k1)xsletsort_by_key_lowfirstxs=sort_prof(fun(k1,v1)(k2,v2)->comparek1k2)xs(*****************************************************************************)(* Assoc *)(*****************************************************************************)type('a,'b)assoc=('a*'b)list(*****************************************************************************)(* Arrays *)(*****************************************************************************)(*****************************************************************************)(* Matrix *)(*****************************************************************************)(*****************************************************************************)(* Set. Have a look too at set*.mli *)(*****************************************************************************)(*****************************************************************************)(* Hash *)(*****************************************************************************)lethash_to_listh=Hashtbl.fold(funkvacc->(k,v)::acc)h[]|>List.sortcomparelethash_of_listxs=leth=Hashtbl.create101inxs|>List.iter(fun(k,v)->Hashtbl.replacehkv);h(*****************************************************************************)(* Hash sets *)(*****************************************************************************)type'ahashset=('a,bool)Hashtbl.t(* with sexp *)lethashset_to_listh=hash_to_listh|>List.mapfst(* old: slightly slower?
* let hashset_of_list xs =
* xs +> List.map (fun x -> x, true) +> hash_of_list
*)lethashset_of_list(xs:'alist):('a,bool)Hashtbl.t=leth=Hashtbl.create(List.lengthxs)inxs|>List.iter(funk->Hashtbl.replacehktrue);hlethkeysh=lethkey=Hashtbl.create101inh|>Hashtbl.iter(funkv->Hashtbl.replacehkeyktrue);hashset_to_listhkeyletgroup_assoc_bykey_eff2xs=leth=Hashtbl.create101inxs|>List.iter(fun(k,v)->Hashtbl.addhkv);letkeys=hkeyshinkeys|>List.map(funk->k,Hashtbl.find_allhk)letgroup_assoc_bykey_effxs=profile_code"Common.group_assoc_bykey_eff"(fun()->group_assoc_bykey_eff2xs)(*****************************************************************************)(* Stack *)(*****************************************************************************)type'astack='alist(* with sexp *)(*****************************************************************************)(* Tree *)(*****************************************************************************)(*****************************************************************************)(* Graph. Have a look too at Ograph_*.mli *)(*****************************************************************************)(*****************************************************************************)(* Generic op *)(*****************************************************************************)letsortxs=List.sortcomparexs(*###########################################################################*)(* Misc functions *)(*###########################################################################*)(*###########################################################################*)(* Postlude *)(*###########################################################################*)(*****************************************************************************)(* Flags and actions *)(*****************************************************************************)(*****************************************************************************)(* Postlude *)(*****************************************************************************)(*****************************************************************************)(* Misc *)(*****************************************************************************)(* now in prelude: exception UnixExit of int *)letexn_to_real_unixexitf=tryf()withUnixExitx->exitxletpp_do_in_zero_boxf=Format.open_box0;f();Format.close_box()letmain_boilerplatef=ifnot(!Sys.interactive)thenexn_to_real_unixexit(fun()->Sys.set_signalSys.sigint(Sys.Signal_handle(fun_->pr2"C-c intercepted, will do some cleaning before exiting";(* But if do some try ... with e -> and if do not reraise the exn,
* the bubble never goes at top and so I cant really C-c.
*
* A solution would be to not raise, but do the erase_temp_file in the
* syshandler, here, and then exit.
* The current solution is to not do some wild try ... with e
* by having in the exn handler a case: UnixExit x -> raise ... | e ->
*)Sys.set_signalSys.sigintSys.Signal_default;raise(UnixExit(-1))));(* The finalize below makes it tedious to go back to exn when use
* 'back' in the debugger. Hence this special case. But the
* Common.debugger will be set in main(), so too late, so
* have to be quicker
*)ifSys.argv|>Array.to_list|>List.exists(funx->x=$="-debugger")thendebugger:=true;finalize(fun()->pp_do_in_zero_box(fun()->tryf();(* <---- here it is *)withUnix.Unix_error(e,fm,argm)->pr2(spf"exn Unix_error: %s %s %s\n"(Unix.error_messagee)fmargm);raise(Unix.Unix_error(e,fm,argm))))(fun()->if!profile<>ProfNonethenbeginpr2(profile_diagnostic());Gc.print_statstderr;end;erase_temp_files();))(* let _ = if not !Sys.interactive then (main ()) *)letfollow_symlinks=reffalseletarg_symlink()=if!follow_symlinksthen" -L "else""letgrep_dash_v_str="| grep -v /.hg/ |grep -v /CVS/ | grep -v /.git/ |grep -v /_darcs/"^"| grep -v /.svn/ | grep -v .git_annot | grep -v .marshall"letfiles_of_dir_or_files_no_vcs_nofilterxs=xs|>List.map(funx->ifis_directoryxthen(* todo: should escape x *)letcmd=(spf"find %s '%s' -type f %s"(* -noleaf *)(arg_symlink())xgrep_dash_v_str)inlet(xs,status)=cmd_to_list_and_statuscmdin(matchstatuswith|Unix.WEXITED0->xs|_->raise(CmdError(status,(spf"CMD = %s, RESULT = %s"cmd(String.concat"\n"xs)))))else[x])|>List.concat(*****************************************************************************)(* Maps *)(*****************************************************************************)moduleSMap=Map.Make(String)type'asmap='aSMap.t