123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526(**************************************************************************)(* *)(* OCaml *)(* *)(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)(* *)(* Copyright 1996 Institut National de Recherche en Informatique et *)(* en Automatique. *)(* *)(* All rights reserved. This file is distributed under the terms of *)(* the GNU Lesser General Public License version 2.1, with the *)(* special exception on linking described in the file LICENSE. *)(* *)(**************************************************************************)(* An alias for the type of lists. *)type'at='alist=[]|(::)of'a*'alist(* List operations *)letreclength_auxlen=function[]->len|_::l->length_aux(len+1)lletlengthl=length_aux0lletconsal=a::llethd=function[]->failwith"hd"|a::_->alettl=function[]->failwith"tl"|_::l->lletnthln=ifn<0theninvalid_arg"List.nth"elseletrecnth_auxln=matchlwith|[]->failwith"nth"|a::l->ifn=0thenaelsenth_auxl(n-1)innth_auxlnletnth_optln=ifn<0theninvalid_arg"List.nth"elseletrecnth_auxln=matchlwith|[]->None|a::l->ifn=0thenSomeaelsenth_auxl(n-1)innth_auxlnletappend=(@)letrecrev_appendl1l2=matchl1with[]->l2|a::l->rev_appendl(a::l2)letrevl=rev_appendl[]letrecinit_tailrec_auxaccinf=ifi>=nthenaccelseinit_tailrec_aux(fi::acc)(i+1)nfletrecinit_auxinf=ifi>=nthen[]elseletr=fiinr::init_aux(i+1)nfletrev_init_threshold=matchSys.backend_typewith|Sys.Native|Sys.Bytecode->10_000(* We don't know the size of the stack, better be safe and assume it's
small. *)|Sys.Other_->50letinitlenf=iflen<0theninvalid_arg"List.init"elseiflen>rev_init_thresholdthenrev(init_tailrec_aux[]0lenf)elseinit_aux0lenfletrecflatten=function[]->[]|l::r->l@flattenrletconcat=flattenletrecmapf=function[]->[]|a::l->letr=fainr::mapflletrecmapiif=function[]->[]|a::l->letr=fiainr::mapi(i+1)flletmapifl=mapi0flletrev_mapfl=letrecrmap_faccu=function|[]->accu|a::l->rmap_f(fa::accu)linrmap_f[]lletreciterf=function[]->()|a::l->fa;iterflletreciteriif=function[]->()|a::l->fia;iteri(i+1)flletiterifl=iteri0flletrecfold_leftfaccul=matchlwith[]->accu|a::l->fold_leftf(faccua)lletrecfold_rightflaccu=matchlwith[]->accu|a::l->fa(fold_rightflaccu)letrecmap2fl1l2=match(l1,l2)with([],[])->[]|(a1::l1,a2::l2)->letr=fa1a2inr::map2fl1l2|(_,_)->invalid_arg"List.map2"letrev_map2fl1l2=letrecrmap2_faccul1l2=match(l1,l2)with|([],[])->accu|(a1::l1,a2::l2)->rmap2_f(fa1a2::accu)l1l2|(_,_)->invalid_arg"List.rev_map2"inrmap2_f[]l1l2letreciter2fl1l2=match(l1,l2)with([],[])->()|(a1::l1,a2::l2)->fa1a2;iter2fl1l2|(_,_)->invalid_arg"List.iter2"letrecfold_left2faccul1l2=match(l1,l2)with([],[])->accu|(a1::l1,a2::l2)->fold_left2f(faccua1a2)l1l2|(_,_)->invalid_arg"List.fold_left2"letrecfold_right2fl1l2accu=match(l1,l2)with([],[])->accu|(a1::l1,a2::l2)->fa1a2(fold_right2fl1l2accu)|(_,_)->invalid_arg"List.fold_right2"letrecfor_allp=function[]->true|a::l->pa&&for_allplletrecexistsp=function[]->false|a::l->pa||existsplletrecfor_all2pl1l2=match(l1,l2)with([],[])->true|(a1::l1,a2::l2)->pa1a2&&for_all2pl1l2|(_,_)->invalid_arg"List.for_all2"letrecexists2pl1l2=match(l1,l2)with([],[])->false|(a1::l1,a2::l2)->pa1a2||exists2pl1l2|(_,_)->invalid_arg"List.exists2"letrecmemx=function[]->false|a::l->compareax=0||memxlletrecmemqx=function[]->false|a::l->a==x||memqxlletrecassocx=function[]->raiseNot_found|(a,b)::l->ifcompareax=0thenbelseassocxlletrecassoc_optx=function[]->None|(a,b)::l->ifcompareax=0thenSomebelseassoc_optxlletrecassqx=function[]->raiseNot_found|(a,b)::l->ifa==xthenbelseassqxlletrecassq_optx=function[]->None|(a,b)::l->ifa==xthenSomebelseassq_optxlletrecmem_assocx=function|[]->false|(a,_)::l->compareax=0||mem_assocxlletrecmem_assqx=function|[]->false|(a,_)::l->a==x||mem_assqxlletrecremove_assocx=function|[]->[]|(a,_aspair)::l->ifcompareax=0thenlelsepair::remove_assocxlletrecremove_assqx=function|[]->[]|(a,_aspair)::l->ifa==xthenlelsepair::remove_assqxlletrecfindp=function|[]->raiseNot_found|x::l->ifpxthenxelsefindplletrecfind_optp=function|[]->None|x::l->ifpxthenSomexelsefind_optplletfind_allp=letrecfindaccu=function|[]->revaccu|x::l->ifpxthenfind(x::accu)lelsefindacculinfind[]letfilter=find_allletfilter_mapf=letrecauxaccu=function|[]->revaccu|x::l->matchfxwith|None->auxaccul|Somev->aux(v::accu)linaux[]letpartitionpl=letrecpartyesno=function|[]->(revyes,revno)|x::l->ifpxthenpart(x::yes)nolelsepartyes(x::no)linpart[][]lletrecsplit=function[]->([],[])|(x,y)::l->let(rx,ry)=splitlin(x::rx,y::ry)letreccombinel1l2=match(l1,l2)with([],[])->[]|(a1::l1,a2::l2)->(a1,a2)::combinel1l2|(_,_)->invalid_arg"List.combine"(** sorting *)letrecmergecmpl1l2=matchl1,l2with|[],l2->l2|l1,[]->l1|h1::t1,h2::t2->ifcmph1h2<=0thenh1::mergecmpt1l2elseh2::mergecmpl1t2letrecchopkl=ifk=0thenlelsebeginmatchlwith|_::t->chop(k-1)t|_->assertfalseendletstable_sortcmpl=letrecrev_mergel1l2accu=matchl1,l2with|[],l2->rev_appendl2accu|l1,[]->rev_appendl1accu|h1::t1,h2::t2->ifcmph1h2<=0thenrev_merget1l2(h1::accu)elserev_mergel1t2(h2::accu)inletrecrev_merge_revl1l2accu=matchl1,l2with|[],l2->rev_appendl2accu|l1,[]->rev_appendl1accu|h1::t1,h2::t2->ifcmph1h2>0thenrev_merge_revt1l2(h1::accu)elserev_merge_revl1t2(h2::accu)inletrecsortnl=matchn,lwith|2,x1::x2::_->ifcmpx1x2<=0then[x1;x2]else[x2;x1]|3,x1::x2::x3::_->ifcmpx1x2<=0thenbeginifcmpx2x3<=0then[x1;x2;x3]elseifcmpx1x3<=0then[x1;x3;x2]else[x3;x1;x2]endelsebeginifcmpx1x3<=0then[x2;x1;x3]elseifcmpx2x3<=0then[x2;x3;x1]else[x3;x2;x1]end|n,l->letn1=nasr1inletn2=n-n1inletl2=chopn1linlets1=rev_sortn1linlets2=rev_sortn2l2inrev_merge_revs1s2[]andrev_sortnl=matchn,lwith|2,x1::x2::_->ifcmpx1x2>0then[x1;x2]else[x2;x1]|3,x1::x2::x3::_->ifcmpx1x2>0thenbeginifcmpx2x3>0then[x1;x2;x3]elseifcmpx1x3>0then[x1;x3;x2]else[x3;x1;x2]endelsebeginifcmpx1x3>0then[x2;x1;x3]elseifcmpx2x3>0then[x2;x3;x1]else[x3;x2;x1]end|n,l->letn1=nasr1inletn2=n-n1inletl2=chopn1linlets1=sortn1linlets2=sortn2l2inrev_merges1s2[]inletlen=lengthliniflen<2thenlelsesortlenlletsort=stable_sortletfast_sort=stable_sort(* Note: on a list of length between about 100000 (depending on the minor
heap size and the type of the list) and Sys.max_array_size, it is
actually faster to use the following, but it might also use more memory
because the argument list cannot be deallocated incrementally.
Also, there seems to be a bug in this code or in the
implementation of obj_truncate.
external obj_truncate : 'a array -> int -> unit = "caml_obj_truncate"
let array_to_list_in_place a =
let l = Array.length a in
let rec loop accu n p =
if p <= 0 then accu else begin
if p = n then begin
obj_truncate a p;
loop (a.(p-1) :: accu) (n-1000) (p-1)
end else begin
loop (a.(p-1) :: accu) n (p-1)
end
end
in
loop [] (l-1000) l
let stable_sort cmp l =
let a = Array.of_list l in
Array.stable_sort cmp a;
array_to_list_in_place a
*)(** sorting + removing duplicates *)letsort_uniqcmpl=letrecrev_mergel1l2accu=matchl1,l2with|[],l2->rev_appendl2accu|l1,[]->rev_appendl1accu|h1::t1,h2::t2->letc=cmph1h2inifc=0thenrev_merget1t2(h1::accu)elseifc<0thenrev_merget1l2(h1::accu)elserev_mergel1t2(h2::accu)inletrecrev_merge_revl1l2accu=matchl1,l2with|[],l2->rev_appendl2accu|l1,[]->rev_appendl1accu|h1::t1,h2::t2->letc=cmph1h2inifc=0thenrev_merge_revt1t2(h1::accu)elseifc>0thenrev_merge_revt1l2(h1::accu)elserev_merge_revl1t2(h2::accu)inletrecsortnl=matchn,lwith|2,x1::x2::_->letc=cmpx1x2inifc=0then[x1]elseifc<0then[x1;x2]else[x2;x1]|3,x1::x2::x3::_->letc=cmpx1x2inifc=0thenbeginletc=cmpx2x3inifc=0then[x2]elseifc<0then[x2;x3]else[x3;x2]endelseifc<0thenbeginletc=cmpx2x3inifc=0then[x1;x2]elseifc<0then[x1;x2;x3]elseletc=cmpx1x3inifc=0then[x1;x2]elseifc<0then[x1;x3;x2]else[x3;x1;x2]endelsebeginletc=cmpx1x3inifc=0then[x2;x1]elseifc<0then[x2;x1;x3]elseletc=cmpx2x3inifc=0then[x2;x1]elseifc<0then[x2;x3;x1]else[x3;x2;x1]end|n,l->letn1=nasr1inletn2=n-n1inletl2=chopn1linlets1=rev_sortn1linlets2=rev_sortn2l2inrev_merge_revs1s2[]andrev_sortnl=matchn,lwith|2,x1::x2::_->letc=cmpx1x2inifc=0then[x1]elseifc>0then[x1;x2]else[x2;x1]|3,x1::x2::x3::_->letc=cmpx1x2inifc=0thenbeginletc=cmpx2x3inifc=0then[x2]elseifc>0then[x2;x3]else[x3;x2]endelseifc>0thenbeginletc=cmpx2x3inifc=0then[x1;x2]elseifc>0then[x1;x2;x3]elseletc=cmpx1x3inifc=0then[x1;x2]elseifc>0then[x1;x3;x2]else[x3;x1;x2]endelsebeginletc=cmpx1x3inifc=0then[x2;x1]elseifc>0then[x2;x1;x3]elseletc=cmpx2x3inifc=0then[x2;x1]elseifc>0then[x2;x3;x1]else[x3;x2;x1]end|n,l->letn1=nasr1inletn2=n-n1inletl2=chopn1linlets1=sortn1linlets2=sortn2l2inrev_merges1s2[]inletlen=lengthliniflen<2thenlelsesortlenlletreccompare_lengthsl1l2=matchl1,l2with|[],[]->0|[],_->-1|_,[]->1|_::l1,_::l2->compare_lengthsl1l2;;letreccompare_length_withln=matchlwith|[]->ifn=0then0elseifn>0then-1else1|_::l->ifn<=0then1elsecompare_length_withl(n-1);;(** {1 Iterators} *)letto_seql=letrecauxl()=matchlwith|[]->Seq.Nil|x::tail->Seq.Cons(x,auxtail)inauxlletof_seqseq=letrecdirectdepthseq:_list=ifdepth=0thenSeq.fold_left(funaccx->x::acc)[]seq|>rev(* tailrec *)elsematchseq()with|Seq.Nil->[]|Seq.Cons(x,next)->x::direct(depth-1)nextindirect500seq