Legend:
Page
Library
Module
Module type
Parameter
Class
Class type
Source
Source file array.ml
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430(**************************************************************************)(* *)(* 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 arrays. *)type'at='aarray(* Array operations *)externallength:'aarray->int="%array_length"externalget:'aarray->int->'a="%array_safe_get"externalset:'aarray->int->'a->unit="%array_safe_set"externalunsafe_get:'aarray->int->'a="%array_unsafe_get"externalunsafe_set:'aarray->int->'a->unit="%array_unsafe_set"externalmake:int->'a->'aarray="caml_make_vect"externalcreate:int->'a->'aarray="caml_make_vect"externalunsafe_sub:'aarray->int->int->'aarray="caml_array_sub"externalappend_prim:'aarray->'aarray->'aarray="caml_array_append"externalconcat:'aarraylist->'aarray="caml_array_concat"externalunsafe_blit:'aarray->int->'aarray->int->int->unit="caml_array_blit"externalunsafe_fill:'aarray->int->int->'a->unit="caml_array_fill"externalcreate_float:int->floatarray="caml_make_float_vect"letmake_float=create_floatmoduleFloatarray=structexternalcreate:int->floatarray="caml_floatarray_create"externallength:floatarray->int="%floatarray_length"externalget:floatarray->int->float="%floatarray_safe_get"externalset:floatarray->int->float->unit="%floatarray_safe_set"externalunsafe_get:floatarray->int->float="%floatarray_unsafe_get"externalunsafe_set:floatarray->int->float->unit="%floatarray_unsafe_set"endletinitlf=ifl=0then[||]elseifl<0theninvalid_arg"Array.init"(* See #6575. We could also check for maximum array size, but this depends
on whether we create a float array or a regular one... *)elseletres=createl(f0)infori=1topredldounsafe_setresi(fi)done;resletmake_matrixsxsyinit=letres=createsx[||]inforx=0topredsxdounsafe_setresx(createsyinit)done;resletcreate_matrix=make_matrixletcopya=letl=lengthainifl=0then[||]elseunsafe_suba0lletappenda1a2=letl1=lengtha1inifl1=0thencopya2elseiflengtha2=0thenunsafe_suba10l1elseappend_prima1a2letsubaofslen=ifofs<0||len<0||ofs>lengtha-lentheninvalid_arg"Array.sub"elseunsafe_subaofslenletfillaofslenv=ifofs<0||len<0||ofs>lengtha-lentheninvalid_arg"Array.fill"elseunsafe_fillaofslenvletblita1ofs1a2ofs2len=iflen<0||ofs1<0||ofs1>lengtha1-len||ofs2<0||ofs2>lengtha2-lentheninvalid_arg"Array.blit"elseunsafe_blita1ofs1a2ofs2lenletiterfa=fori=0tolengtha-1dof(unsafe_getai)doneletiter2fab=iflengtha<>lengthbtheninvalid_arg"Array.iter2: arrays must have the same length"elsefori=0tolengtha-1dof(unsafe_getai)(unsafe_getbi)doneletmapfa=letl=lengthainifl=0then[||]elsebeginletr=createl(f(unsafe_geta0))infori=1tol-1dounsafe_setri(f(unsafe_getai))done;rendletmap2fab=letla=lengthainletlb=lengthbinifla<>lbtheninvalid_arg"Array.map2: arrays must have the same length"elsebeginifla=0then[||]elsebeginletr=createla(f(unsafe_geta0)(unsafe_getb0))infori=1tola-1dounsafe_setri(f(unsafe_getai)(unsafe_getbi))done;rendendletiterifa=fori=0tolengtha-1dofi(unsafe_getai)doneletmapifa=letl=lengthainifl=0then[||]elsebeginletr=createl(f0(unsafe_geta0))infori=1tol-1dounsafe_setri(fi(unsafe_getai))done;rendletto_lista=letrectolistires=ifi<0thenreselsetolist(i-1)(unsafe_getai::res)intolist(lengtha-1)[](* Cannot use List.length here because the List module depends on Array. *)letreclist_lengthaccu=function|[]->accu|_::t->list_length(succaccu)tletof_list=function[]->[||]|hd::tlasl->leta=create(list_length0l)hdinletrecfilli=function[]->a|hd::tl->unsafe_setaihd;fill(i+1)tlinfill1tlletfold_leftfxa=letr=refxinfori=0tolengtha-1dor:=f!r(unsafe_getai)done;!rletfold_left_mapfaccinput_array=letlen=lengthinput_arrayiniflen=0then(acc,[||])elsebeginletacc,elt=facc(unsafe_getinput_array0)inletoutput_array=createleneltinletacc=refaccinfori=1tolen-1doletacc',elt=f!acc(unsafe_getinput_arrayi)inacc:=acc';unsafe_setoutput_arrayielt;done;!acc,output_arrayendletfold_rightfax=letr=refxinfori=lengtha-1downto0dor:=f(unsafe_getai)!rdone;!rletexistspa=letn=lengthainletrecloopi=ifi=nthenfalseelseifp(unsafe_getai)thentrueelseloop(succi)inloop0letfor_allpa=letn=lengthainletrecloopi=ifi=nthentrueelseifp(unsafe_getai)thenloop(succi)elsefalseinloop0letfor_all2pl1l2=letn1=lengthl1andn2=lengthl2inifn1<>n2theninvalid_arg"Array.for_all2"elseletrecloopi=ifi=n1thentrueelseifp(unsafe_getl1i)(unsafe_getl2i)thenloop(succi)elsefalseinloop0letexists2pl1l2=letn1=lengthl1andn2=lengthl2inifn1<>n2theninvalid_arg"Array.exists2"elseletrecloopi=ifi=n1thenfalseelseifp(unsafe_getl1i)(unsafe_getl2i)thentrueelseloop(succi)inloop0letmemxa=letn=lengthainletrecloopi=ifi=nthenfalseelseifcompare(unsafe_getai)x=0thentrueelseloop(succi)inloop0letmemqxa=letn=lengthainletrecloopi=ifi=nthenfalseelseifx==(unsafe_getai)thentrueelseloop(succi)inloop0letfind_optpa=letn=lengthainletrecloopi=ifi=nthenNoneelseletx=unsafe_getaiinifpxthenSomexelseloop(succi)inloop0letfind_mapfa=letn=lengthainletrecloopi=ifi=nthenNoneelsematchf(unsafe_getai)with|None->loop(succi)|Some_asr->rinloop0letsplitx=ifx=[||]then[||],[||]elsebeginleta0,b0=unsafe_getx0inletn=lengthxinleta=createna0inletb=createnb0infori=1ton-1doletai,bi=unsafe_getxiinunsafe_setaiai;unsafe_setbibidone;a,bendletcombineab=letna=lengthainletnb=lengthbinifna<>nbtheninvalid_arg"Array.combine";ifna=0then[||]elsebeginletx=createna(unsafe_geta0,unsafe_getb0)infori=1tona-1dounsafe_setxi(unsafe_getai,unsafe_getbi)done;xendexceptionBottomofintletsortcmpa=letmaxsonli=leti31=i+i+i+1inletx=refi31inifi31+2<lthenbeginifcmp(getai31)(geta(i31+1))<0thenx:=i31+1;ifcmp(geta!x)(geta(i31+2))<0thenx:=i31+2;!xendelseifi31+1<l&&cmp(getai31)(geta(i31+1))<0theni31+1elseifi31<ltheni31elseraise(Bottomi)inletrectrickledownlie=letj=maxsonliinifcmp(getaj)e>0thenbeginsetai(getaj);trickledownlje;endelsebeginsetaie;end;inlettricklelie=trytrickledownliewithBottomi->setaieinletrecbubbledownli=letj=maxsonliinsetai(getaj);bubbledownljinletbubbleli=trybubbledownliwithBottomi->iinletrectrickleupie=letfather=(i-1)/3inassert(i<>father);ifcmp(getafather)e<0thenbeginsetai(getafather);iffather>0thentrickleupfathereelseseta0e;endelsebeginsetaie;end;inletl=lengthainfori=(l+1)/3-1downto0dotrickleli(getai);done;fori=l-1downto2dolete=(getai)insetai(geta0);trickleup(bubblei0)e;done;ifl>1then(lete=(geta1)inseta1(geta0);seta0e)letcutoff=5letstable_sortcmpa=letmergesrc1ofssrc1lensrc2src2ofssrc2lendstdstofs=letsrc1r=src1ofs+src1lenandsrc2r=src2ofs+src2leninletrecloopi1s1i2s2d=ifcmps1s2<=0thenbeginsetdstds1;leti1=i1+1inifi1<src1rthenloopi1(getai1)i2s2(d+1)elseblitsrc2i2dst(d+1)(src2r-i2)endelsebeginsetdstds2;leti2=i2+1inifi2<src2rthenloopi1s1i2(getsrc2i2)(d+1)elseblitai1dst(d+1)(src1r-i1)endinloopsrc1ofs(getasrc1ofs)src2ofs(getsrc2src2ofs)dstofs;inletisorttosrcofsdstdstofslen=fori=0tolen-1dolete=(geta(srcofs+i))inletj=ref(dstofs+i-1)inwhile(!j>=dstofs&&cmp(getdst!j)e>0)dosetdst(!j+1)(getdst!j);decrj;done;setdst(!j+1)e;done;inletrecsorttosrcofsdstdstofslen=iflen<=cutoffthenisorttosrcofsdstdstofslenelsebeginletl1=len/2inletl2=len-l1insortto(srcofs+l1)dst(dstofs+l1)l2;sorttosrcofsa(srcofs+l2)l1;merge(srcofs+l2)l1dst(dstofs+l1)l2dstdstofs;end;inletl=lengthainifl<=cutoffthenisortto0a0lelsebeginletl1=l/2inletl2=l-l1inlett=makel2(geta0)insorttol1t0l2;sortto0al2l1;mergel2l1t0l2a0;endletfast_sort=stable_sort(** {1 Iterators} *)letto_seqa=letrecauxi()=ifi<lengthathenletx=unsafe_getaiinSeq.Cons(x,aux(i+1))elseSeq.Nilinaux0letto_seqia=letrecauxi()=ifi<lengthathenletx=unsafe_getaiinSeq.Cons((i,x),aux(i+1))elseSeq.Nilinaux0letof_rev_list=function[]->[||]|hd::tlasl->letlen=list_length0linleta=createlenhdinletrecfilli=function[]->a|hd::tl->unsafe_setaihd;fill(i-1)tlinfill(len-2)tlletof_seqi=letl=Seq.fold_left(funaccx->x::acc)[]iinof_rev_listl