Legend:
Page
Library
Module
Module type
Parameter
Class
Class type
Source
Source file hashtbl.ml
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613(**************************************************************************)(* *)(* 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. *)(* *)(**************************************************************************)(* Hash tables *)(* We do dynamic hashing, and resize the table and rehash the elements
when buckets become too long. *)type('a,'b)t={mutablesize:int;(* number of entries *)mutabledata:('a,'b)bucketlistarray;(* the buckets *)mutableseed:int;(* for randomization *)mutableinitial_size:int;(* initial array size *)}and('a,'b)bucketlist=Empty|Consof{mutablekey:'a;mutabledata:'b;mutablenext:('a,'b)bucketlist}(* The sign of initial_size encodes the fact that a traversal is
ongoing or not.
This disables the efficient in place implementation of resizing.
*)letongoing_traversalh=Obj.size(Obj.reprh)<4(* compatibility with old hash tables *)||h.initial_size<0letflip_ongoing_traversalh=h.initial_size<--h.initial_size(* To pick random seeds if requested *)letrandomized_default=letparams=trySys.getenv"OCAMLRUNPARAM"withNot_found->trySys.getenv"CAMLRUNPARAM"withNot_found->""inString.containsparams'R'letrandomized=refrandomized_defaultletrandomize()=randomized:=trueletis_randomized()=!randomizedletprng=lazy(Random.State.make_self_init())(* Functions which appear before the functorial interface must either be
independent of the hash function or take it as a parameter (see #2202 and
code below the functor definitions. *)(* Creating a fresh, empty table *)letrecpower_2_abovexn=ifx>=nthenxelseifx*2>Sys.max_array_lengththenxelsepower_2_above(x*2)nletcreate?(random=!randomized)initial_size=lets=power_2_above16initial_sizeinletseed=ifrandomthenRandom.State.bits(Lazy.forceprng)else0in{initial_size=s;size=0;seed=seed;data=Array.makesEmpty}letclearh=ifh.size>0thenbeginh.size<-0;Array.fillh.data0(Array.lengthh.data)Emptyendletreseth=letlen=Array.lengthh.datainifObj.size(Obj.reprh)<4(* compatibility with old hash tables *)||len=absh.initial_sizethenclearhelsebeginh.size<-0;h.data<-Array.make(absh.initial_size)Emptyendletcopy_bucketlist=function|Empty->Empty|Cons{key;data;next}->letrecloopprec=function|Empty->()|Cons{key;data;next}->letr=Cons{key;data;next}inbeginmatchprecwith|Empty->assertfalse|Consprec->prec.next<-rend;looprnextinletr=Cons{key;data;next}inlooprnext;rletcopyh={hwithdata=Array.mapcopy_bucketlisth.data}letlengthh=h.sizeletresizeindexfunh=letodata=h.datainletosize=Array.lengthodatainletnsize=osize*2inifnsize<Sys.max_array_lengththenbeginletndata=Array.makensizeEmptyinletndata_tail=Array.makensizeEmptyinletinplace=not(ongoing_traversalh)inh.data<-ndata;(* so that indexfun sees the new bucket count *)letrecinsert_bucket=function|Empty->()|Cons{key;data;next}ascell->letcell=ifinplacethencellelseCons{key;data;next=Empty}inletnidx=indexfunhkeyinbeginmatchndata_tail.(nidx)with|Empty->ndata.(nidx)<-cell;|Constail->tail.next<-cell;end;ndata_tail.(nidx)<-cell;insert_bucketnextinfori=0toosize-1doinsert_bucketodata.(i)done;ifinplacethenfori=0tonsize-1domatchndata_tail.(i)with|Empty->()|Constail->tail.next<-Emptydone;endletiterfh=letrecdo_bucket=function|Empty->()|Cons{key;data;next}->fkeydata;do_bucketnextinletold_trav=ongoing_traversalhinifnotold_travthenflip_ongoing_traversalh;tryletd=h.datainfori=0toArray.lengthd-1dodo_bucketd.(i)done;ifnotold_travthenflip_ongoing_traversalh;withexnwhennotold_trav->flip_ongoing_traversalh;raiseexnletrecfilter_map_inplace_bucketfhiprec=function|Empty->beginmatchprecwith|Empty->h.data.(i)<-Empty|Consc->c.next<-Emptyend|(Cons({key;data;next}asc))asslot->beginmatchfkeydatawith|None->h.size<-h.size-1;filter_map_inplace_bucketfhiprecnext|Somedata->beginmatchprecwith|Empty->h.data.(i)<-slot|Consc->c.next<-slotend;c.data<-data;filter_map_inplace_bucketfhislotnextendletfilter_map_inplacefh=letd=h.datainletold_trav=ongoing_traversalhinifnotold_travthenflip_ongoing_traversalh;tryfori=0toArray.lengthd-1dofilter_map_inplace_bucketfhiEmptyh.data.(i)donewithexnwhennotold_trav->flip_ongoing_traversalh;raiseexnletfoldfhinit=letrecdo_bucketbaccu=matchbwithEmpty->accu|Cons{key;data;next}->do_bucketnext(fkeydataaccu)inletold_trav=ongoing_traversalhinifnotold_travthenflip_ongoing_traversalh;tryletd=h.datainletaccu=refinitinfori=0toArray.lengthd-1doaccu:=do_bucketd.(i)!accudone;ifnotold_travthenflip_ongoing_traversalh;!accuwithexnwhennotold_trav->flip_ongoing_traversalh;raiseexntypestatistics={num_bindings:int;num_buckets:int;max_bucket_length:int;bucket_histogram:intarray}letrecbucket_lengthaccu=function|Empty->accu|Cons{next}->bucket_length(accu+1)nextletstatsh=letmbl=Array.fold_left(funmb->maxm(bucket_length0b))0h.datainlethisto=Array.make(mbl+1)0inArray.iter(funb->letl=bucket_length0binhisto.(l)<-histo.(l)+1)h.data;{num_bindings=h.size;num_buckets=Array.lengthh.data;max_bucket_length=mbl;bucket_histogram=histo}(** {1 Iterators} *)letto_seqtbl=(* capture current array, so that even if the table is resized we
keep iterating on the same array *)lettbl_data=tbl.datain(* state: index * next bucket to traverse *)letrecauxibuck()=matchbuckwith|Empty->ifi=Array.lengthtbl_datathenSeq.Nilelseaux(i+1)tbl_data.(i)()|Cons{key;data;next}->Seq.Cons((key,data),auxinext)inaux0Emptyletto_seq_keysm=Seq.mapfst(to_seqm)letto_seq_valuesm=Seq.mapsnd(to_seqm)(* Functorial interface *)moduletypeHashedType=sigtypetvalequal:t->t->boolvalhash:t->intendmoduletypeSeededHashedType=sigtypetvalequal:t->t->boolvalhash:int->t->intendmoduletypeS=sigtypekeytype'atvalcreate:int->'atvalclear:'at->unitvalreset:'at->unitvalcopy:'at->'atvaladd:'at->key->'a->unitvalremove:'at->key->unitvalfind:'at->key->'avalfind_opt:'at->key->'aoptionvalfind_all:'at->key->'alistvalreplace:'at->key->'a->unitvalmem:'at->key->boolvaliter:(key->'a->unit)->'at->unitvalfilter_map_inplace:(key->'a->'aoption)->'at->unitvalfold:(key->'a->'b->'b)->'at->'b->'bvallength:'at->intvalstats:'at->statisticsvalto_seq:'at->(key*'a)Seq.tvalto_seq_keys:_t->keySeq.tvalto_seq_values:'at->'aSeq.tvaladd_seq:'at->(key*'a)Seq.t->unitvalreplace_seq:'at->(key*'a)Seq.t->unitvalof_seq:(key*'a)Seq.t->'atendmoduletypeSeededS=sigtypekeytype'atvalcreate:?random:bool->int->'atvalclear:'at->unitvalreset:'at->unitvalcopy:'at->'atvaladd:'at->key->'a->unitvalremove:'at->key->unitvalfind:'at->key->'avalfind_opt:'at->key->'aoptionvalfind_all:'at->key->'alistvalreplace:'at->key->'a->unitvalmem:'at->key->boolvaliter:(key->'a->unit)->'at->unitvalfilter_map_inplace:(key->'a->'aoption)->'at->unitvalfold:(key->'a->'b->'b)->'at->'b->'bvallength:'at->intvalstats:'at->statisticsvalto_seq:'at->(key*'a)Seq.tvalto_seq_keys:_t->keySeq.tvalto_seq_values:'at->'aSeq.tvaladd_seq:'at->(key*'a)Seq.t->unitvalreplace_seq:'at->(key*'a)Seq.t->unitvalof_seq:(key*'a)Seq.t->'atendmoduleMakeSeeded(H:SeededHashedType):(SeededSwithtypekey=H.t)=structtypekey=H.ttype'ahashtbl=(key,'a)ttype'at='ahashtblletcreate=createletclear=clearletreset=resetletcopy=copyletkey_indexhkey=(H.hashh.seedkey)land(Array.lengthh.data-1)letaddhkeydata=leti=key_indexhkeyinletbucket=Cons{key;data;next=h.data.(i)}inh.data.(i)<-bucket;h.size<-h.size+1;ifh.size>Array.lengthh.datalsl1thenresizekey_indexhletrecremove_buckethikeyprec=function|Empty->()|(Cons{key=k;next})asc->ifH.equalkkeythenbeginh.size<-h.size-1;matchprecwith|Empty->h.data.(i)<-next|Consc->c.next<-nextendelseremove_buckethikeycnextletremovehkey=leti=key_indexhkeyinremove_buckethikeyEmptyh.data.(i)letrecfind_reckey=function|Empty->raiseNot_found|Cons{key=k;data;next}->ifH.equalkeykthendataelsefind_reckeynextletfindhkey=matchh.data.(key_indexhkey)with|Empty->raiseNot_found|Cons{key=k1;data=d1;next=next1}->ifH.equalkeyk1thend1elsematchnext1with|Empty->raiseNot_found|Cons{key=k2;data=d2;next=next2}->ifH.equalkeyk2thend2elsematchnext2with|Empty->raiseNot_found|Cons{key=k3;data=d3;next=next3}->ifH.equalkeyk3thend3elsefind_reckeynext3letrecfind_rec_optkey=function|Empty->None|Cons{key=k;data;next}->ifH.equalkeykthenSomedataelsefind_rec_optkeynextletfind_opthkey=matchh.data.(key_indexhkey)with|Empty->None|Cons{key=k1;data=d1;next=next1}->ifH.equalkeyk1thenSomed1elsematchnext1with|Empty->None|Cons{key=k2;data=d2;next=next2}->ifH.equalkeyk2thenSomed2elsematchnext2with|Empty->None|Cons{key=k3;data=d3;next=next3}->ifH.equalkeyk3thenSomed3elsefind_rec_optkeynext3letfind_allhkey=letrecfind_in_bucket=function|Empty->[]|Cons{key=k;data=d;next}->ifH.equalkkeythend::find_in_bucketnextelsefind_in_bucketnextinfind_in_bucketh.data.(key_indexhkey)letrecreplace_bucketkeydata=function|Empty->true|Cons({key=k;next}asslot)->ifH.equalkkeythen(slot.key<-key;slot.data<-data;false)elsereplace_bucketkeydatanextletreplacehkeydata=leti=key_indexhkeyinletl=h.data.(i)inifreplace_bucketkeydatalthenbeginh.data.(i)<-Cons{key;data;next=l};h.size<-h.size+1;ifh.size>Array.lengthh.datalsl1thenresizekey_indexhendletmemhkey=letrecmem_in_bucket=function|Empty->false|Cons{key=k;next}->H.equalkkey||mem_in_bucketnextinmem_in_bucketh.data.(key_indexhkey)letadd_seqtbli=Seq.iter(fun(k,v)->addtblkv)iletreplace_seqtbli=Seq.iter(fun(k,v)->replacetblkv)iletof_seqi=lettbl=create16inreplace_seqtbli;tblletiter=iterletfilter_map_inplace=filter_map_inplaceletfold=foldletlength=lengthletstats=statsletto_seq=to_seqletto_seq_keys=to_seq_keysletto_seq_values=to_seq_valuesendmoduleMake(H:HashedType):(Swithtypekey=H.t)=structincludeMakeSeeded(structtypet=H.tletequal=H.equallethash(_seed:int)x=H.hashxend)letcreatesz=create~random:falseszletof_seqi=lettbl=create16inreplace_seqtbli;tblend(* Polymorphic hash function-based tables *)(* Code included below the functorial interface to guard against accidental
use - see #2202 *)externalseeded_hash_param:int->int->int->'a->int="caml_hash"[@@noalloc]externalold_hash_param:int->int->'a->int="caml_hash_univ_param"[@@noalloc]lethashx=seeded_hash_param101000xlethash_paramn1n2x=seeded_hash_paramn1n20xletseeded_hashseedx=seeded_hash_param10100seedxletkey_indexhkey=(* compatibility with old hash tables *)ifObj.size(Obj.reprh)>=3then(seeded_hash_param10100h.seedkey)land(Array.lengthh.data-1)else(old_hash_param10100key)mod(Array.lengthh.data)letaddhkeydata=leti=key_indexhkeyinletbucket=Cons{key;data;next=h.data.(i)}inh.data.(i)<-bucket;h.size<-h.size+1;ifh.size>Array.lengthh.datalsl1thenresizekey_indexhletrecremove_buckethikeyprec=function|Empty->()|(Cons{key=k;next})asc->ifcomparekkey=0thenbeginh.size<-h.size-1;matchprecwith|Empty->h.data.(i)<-next|Consc->c.next<-nextendelseremove_buckethikeycnextletremovehkey=leti=key_indexhkeyinremove_buckethikeyEmptyh.data.(i)letrecfind_reckey=function|Empty->raiseNot_found|Cons{key=k;data;next}->ifcomparekeyk=0thendataelsefind_reckeynextletfindhkey=matchh.data.(key_indexhkey)with|Empty->raiseNot_found|Cons{key=k1;data=d1;next=next1}->ifcomparekeyk1=0thend1elsematchnext1with|Empty->raiseNot_found|Cons{key=k2;data=d2;next=next2}->ifcomparekeyk2=0thend2elsematchnext2with|Empty->raiseNot_found|Cons{key=k3;data=d3;next=next3}->ifcomparekeyk3=0thend3elsefind_reckeynext3letrecfind_rec_optkey=function|Empty->None|Cons{key=k;data;next}->ifcomparekeyk=0thenSomedataelsefind_rec_optkeynextletfind_opthkey=matchh.data.(key_indexhkey)with|Empty->None|Cons{key=k1;data=d1;next=next1}->ifcomparekeyk1=0thenSomed1elsematchnext1with|Empty->None|Cons{key=k2;data=d2;next=next2}->ifcomparekeyk2=0thenSomed2elsematchnext2with|Empty->None|Cons{key=k3;data=d3;next=next3}->ifcomparekeyk3=0thenSomed3elsefind_rec_optkeynext3letfind_allhkey=letrecfind_in_bucket=function|Empty->[]|Cons{key=k;data;next}->ifcomparekkey=0thendata::find_in_bucketnextelsefind_in_bucketnextinfind_in_bucketh.data.(key_indexhkey)letrecreplace_bucketkeydata=function|Empty->true|Cons({key=k;next}asslot)->ifcomparekkey=0then(slot.key<-key;slot.data<-data;false)elsereplace_bucketkeydatanextletreplacehkeydata=leti=key_indexhkeyinletl=h.data.(i)inifreplace_bucketkeydatalthenbeginh.data.(i)<-Cons{key;data;next=l};h.size<-h.size+1;ifh.size>Array.lengthh.datalsl1thenresizekey_indexhendletmemhkey=letrecmem_in_bucket=function|Empty->false|Cons{key=k;next}->comparekkey=0||mem_in_bucketnextinmem_in_bucketh.data.(key_indexhkey)letadd_seqtbli=Seq.iter(fun(k,v)->addtblkv)iletreplace_seqtbli=Seq.iter(fun(k,v)->replacetblkv)iletof_seqi=lettbl=create16inreplace_seqtbli;tbl