123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359(**************************************************************************)(* *)(* OCaml *)(* *)(* Pierre Weis and Xavier Leroy, projet Cristal, INRIA Rocquencourt *)(* *)(* Copyright 1999 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. *)(* *)(**************************************************************************)(* Extensible buffers *)typet={mutablebuffer:bytes;mutableposition:int;mutablelength:int;initial_buffer:bytes}letcreaten=letn=ifn<1then1elseninletn=ifn>Sys.max_string_lengththenSys.max_string_lengthelseninlets=Bytes.createnin{buffer=s;position=0;length=n;initial_buffer=s}letcontentsb=Bytes.sub_stringb.buffer0b.positionletto_bytesb=Bytes.subb.buffer0b.positionletsubbofslen=ifofs<0||len<0||ofs>b.position-lentheninvalid_arg"Buffer.sub"elseBytes.sub_stringb.bufferofslenletblitsrcsrcoffdstdstofflen=iflen<0||srcoff<0||srcoff>src.position-len||dstoff<0||dstoff>(Bytes.lengthdst)-lentheninvalid_arg"Buffer.blit"elseBytes.unsafe_blitsrc.buffersrcoffdstdstofflenletnthbofs=ifofs<0||ofs>=b.positiontheninvalid_arg"Buffer.nth"elseBytes.unsafe_getb.bufferofsletlengthb=b.positionletclearb=b.position<-0letresetb=b.position<-0;b.buffer<-b.initial_buffer;b.length<-Bytes.lengthb.bufferletresizebmore=letlen=b.lengthinletnew_len=refleninwhileb.position+more>!new_lendonew_len:=2*!new_lendone;if!new_len>Sys.max_string_lengththenbeginifb.position+more<=Sys.max_string_lengththennew_len:=Sys.max_string_lengthelsefailwith"Buffer.add: cannot grow buffer"end;letnew_buffer=Bytes.create!new_lenin(* PR#6148: let's keep using [blit] rather than [unsafe_blit] in
this tricky function that is slow anyway. *)Bytes.blitb.buffer0new_buffer0b.position;b.buffer<-new_buffer;b.length<-!new_lenletadd_charbc=letpos=b.positioninifpos>=b.lengththenresizeb1;Bytes.unsafe_setb.bufferposc;b.position<-pos+1letadd_utf_8_ucharbu=matchUchar.to_intuwith|uwhenu<0->assertfalse|uwhenu<=0x007F->add_charb(Char.unsafe_chru)|uwhenu<=0x07FF->letpos=b.positioninifpos+2>b.lengththenresizeb2;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(0xC0lor(ulsr6)));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(0x80lor(uland0x3F)));b.position<-pos+2|uwhenu<=0xFFFF->letpos=b.positioninifpos+3>b.lengththenresizeb3;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(0xE0lor(ulsr12)));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(0x80lor((ulsr6)land0x3F)));Bytes.unsafe_setb.buffer(pos+2)(Char.unsafe_chr(0x80lor(uland0x3F)));b.position<-pos+3|uwhenu<=0x10FFFF->letpos=b.positioninifpos+4>b.lengththenresizeb4;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(0xF0lor(ulsr18)));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(0x80lor((ulsr12)land0x3F)));Bytes.unsafe_setb.buffer(pos+2)(Char.unsafe_chr(0x80lor((ulsr6)land0x3F)));Bytes.unsafe_setb.buffer(pos+3)(Char.unsafe_chr(0x80lor(uland0x3F)));b.position<-pos+4|_->assertfalseletadd_utf_16be_ucharbu=matchUchar.to_intuwith|uwhenu<0->assertfalse|uwhenu<=0xFFFF->letpos=b.positioninifpos+2>b.lengththenresizeb2;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(ulsr8));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(uland0xFF));b.position<-pos+2|uwhenu<=0x10FFFF->letu'=u-0x10000inlethi=0xD800lor(u'lsr10)inletlo=0xDC00lor(u'land0x3FF)inletpos=b.positioninifpos+4>b.lengththenresizeb4;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(hilsr8));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(hiland0xFF));Bytes.unsafe_setb.buffer(pos+2)(Char.unsafe_chr(lolsr8));Bytes.unsafe_setb.buffer(pos+3)(Char.unsafe_chr(loland0xFF));b.position<-pos+4|_->assertfalseletadd_utf_16le_ucharbu=matchUchar.to_intuwith|uwhenu<0->assertfalse|uwhenu<=0xFFFF->letpos=b.positioninifpos+2>b.lengththenresizeb2;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(uland0xFF));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(ulsr8));b.position<-pos+2|uwhenu<=0x10FFFF->letu'=u-0x10000inlethi=0xD800lor(u'lsr10)inletlo=0xDC00lor(u'land0x3FF)inletpos=b.positioninifpos+4>b.lengththenresizeb4;Bytes.unsafe_setb.buffer(pos)(Char.unsafe_chr(hiland0xFF));Bytes.unsafe_setb.buffer(pos+1)(Char.unsafe_chr(hilsr8));Bytes.unsafe_setb.buffer(pos+2)(Char.unsafe_chr(loland0xFF));Bytes.unsafe_setb.buffer(pos+3)(Char.unsafe_chr(lolsr8));b.position<-pos+4|_->assertfalseletadd_substringbsoffsetlen=ifoffset<0||len<0||offset>String.lengths-lentheninvalid_arg"Buffer.add_substring/add_subbytes";letnew_position=b.position+leninifnew_position>b.lengththenresizeblen;Bytes.blit_stringsoffsetb.bufferb.positionlen;b.position<-new_positionletadd_subbytesbsoffsetlen=add_substringb(Bytes.unsafe_to_strings)offsetlenletadd_stringbs=letlen=String.lengthsinletnew_position=b.position+leninifnew_position>b.lengththenresizeblen;Bytes.blit_strings0b.bufferb.positionlen;b.position<-new_positionletadd_bytesbs=add_stringb(Bytes.unsafe_to_strings)letadd_bufferbbs=add_subbytesbbs.buffer0bs.position(* read up to [len] bytes from [ic] into [b]. *)letrecadd_channel_recbiclen=iflen>0then(letn=inputicb.bufferb.positionleninb.position<-b.position+n;ifn=0thenraiseEnd_of_fileelseadd_channel_recbic(len-n)(* n <= len *))letadd_channelbiclen=iflen<0||len>Sys.max_string_lengththen(* PR#5004 *)invalid_arg"Buffer.add_channel";ifb.position+len>b.lengththenresizeblen;add_channel_recbiclenletoutput_bufferocb=outputocb.buffer0b.positionletclosing=function|'('->')'|'{'->'}'|_->assertfalse(* opening and closing: open and close characters, typically ( and )
k: balance of opening and closing chars
s: the string where we are searching
start: the index where we start the search. *)letadvance_to_closingopeningclosingksstart=letrecadvancekilim=ifi>=limthenraiseNot_foundelseifs.[i]=openingthenadvance(k+1)(i+1)limelseifs.[i]=closingthenifk=0thenielseadvance(k-1)(i+1)limelseadvancek(i+1)liminadvancekstart(String.lengths)letadvance_to_non_alphasstart=letrecadvanceilim=ifi>=limthenlimelsematchs.[i]with|'a'..'z'|'A'..'Z'|'0'..'9'|'_'->advance(i+1)lim|_->iinadvancestart(String.lengths)(* We are just at the beginning of an ident in s, starting at start. *)letfind_identsstartlim=ifstart>=limthenraiseNot_foundelsematchs.[start]with(* Parenthesized ident ? *)|'('|'{'asc->letnew_start=start+1inletstop=advance_to_closingc(closingc)0snew_startinString.subsnew_start(stop-start-1),stop+1(* Regular ident *)|_->letstop=advance_to_non_alphas(start+1)inString.subsstart(stop-start),stop(* Substitute $ident, $(ident), or ${ident} in s,
according to the function mapping f. *)letadd_substitutebfs=letlim=String.lengthsinletrecsubstpreviousi=ifi<limthenbeginmatchs.[i]with|'$'ascurrentwhenprevious='\\'->add_charbcurrent;subst' '(i+1)|'$'->letj=i+1inletident,next_i=find_identsjliminadd_stringb(fident);subst' 'next_i|currentwhenprevious=='\\'->add_charb'\\';add_charbcurrent;subst' '(i+1)|'\\'ascurrent->substcurrent(i+1)|current->add_charbcurrent;substcurrent(i+1)endelseifprevious='\\'thenadd_charbpreviousinsubst' '0lettruncateblen=iflen<0||len>lengthbtheninvalid_arg"Buffer.truncate"elseb.position<-len(** {1 Iterators} *)letto_seqb=letrecauxi()=ifi>=b.positionthenSeq.Nilelseletx=Bytes.getb.bufferiinSeq.Cons(x,aux(i+1))inaux0letto_seqib=letrecauxi()=ifi>=b.positionthenSeq.Nilelseletx=Bytes.getb.bufferiinSeq.Cons((i,x),aux(i+1))inaux0letadd_seqbseq=Seq.iter(add_charb)seqletof_seqi=letb=create32inadd_seqbi;b(** {6 Binary encoding of integers} *)externalunsafe_set_int8:bytes->int->int->unit="%bytes_unsafe_set"externalunsafe_set_int16:bytes->int->int->unit="%caml_bytes_set16u"externalunsafe_set_int32:bytes->int->int32->unit="%caml_bytes_set32u"externalunsafe_set_int64:bytes->int->int64->unit="%caml_bytes_set64u"externalswap16:int->int="%bswap16"externalswap32:int32->int32="%bswap_int32"externalswap64:int64->int64="%bswap_int64"letadd_int8bx=letnew_position=b.position+1inifnew_position>b.lengththenresizeb1;unsafe_set_int8b.bufferb.positionx;b.position<-new_positionletadd_int16_nebx=letnew_position=b.position+2inifnew_position>b.lengththenresizeb2;unsafe_set_int16b.bufferb.positionx;b.position<-new_positionletadd_int32_nebx=letnew_position=b.position+4inifnew_position>b.lengththenresizeb4;unsafe_set_int32b.bufferb.positionx;b.position<-new_positionletadd_int64_nebx=letnew_position=b.position+8inifnew_position>b.lengththenresizeb8;unsafe_set_int64b.bufferb.positionx;b.position<-new_positionletadd_int16_lebx=add_int16_neb(ifSys.big_endianthenswap16xelsex)letadd_int16_bebx=add_int16_neb(ifSys.big_endianthenxelseswap16x)letadd_int32_lebx=add_int32_neb(ifSys.big_endianthenswap32xelsex)letadd_int32_bebx=add_int32_neb(ifSys.big_endianthenxelseswap32x)letadd_int64_lebx=add_int64_neb(ifSys.big_endianthenswap64xelsex)letadd_int64_bebx=add_int64_neb(ifSys.big_endianthenxelseswap64x)letadd_uint8=add_int8letadd_uint16_ne=add_int16_neletadd_uint16_le=add_int16_leletadd_uint16_be=add_int16_be