@@ -44,12 +44,20 @@ CAMLprim value caml_ml_string_length(value s)
4444 return Val_long (temp - Byte (s , temp ));
4545}
4646
47+ CAMLprim value caml_ml_bytes_length (value s )
48+ {
49+ return caml_ml_string_length (s );
50+ }
51+
4752CAMLexport int caml_string_is_c_safe (value s )
4853{
4954 return strlen (String_val (s )) == caml_string_length (s );
5055}
5156
52- /* [len] is a value that represents a number of bytes (chars) */
57+ /**
58+ * [caml_create_string] is deprecated,
59+ * use [caml_create_bytes] instead
60+ */
5361CAMLprim value caml_create_string (value len )
5462{
5563 mlsize_t size = Long_val (len );
@@ -59,13 +67,29 @@ CAMLprim value caml_create_string(value len)
5967 return caml_alloc_string (size );
6068}
6169
70+ /* [len] is a value that represents a number of bytes (chars) */
71+ CAMLprim value caml_create_bytes (value len )
72+ {
73+ mlsize_t size = Long_val (len );
74+ if (size > Bsize_wsize (Max_wosize ) - 1 ){
75+ caml_invalid_argument ("Bytes.create" );
76+ }
77+ return caml_alloc_string (size );
78+ }
79+
80+
81+
6282CAMLprim value caml_string_get (value str , value index )
6383{
6484 intnat idx = Long_val (index );
6585 if (idx < 0 || idx >= caml_string_length (str )) caml_array_bound_error ();
6686 return Val_int (Byte_u (str , idx ));
6787}
6888
89+ CAMLprim value caml_bytes_get (value str , value index )
90+ {
91+ return caml_string_get (str , index );
92+ }
6993CAMLprim value caml_string_set (value str , value index , value newval )
7094{
7195 intnat idx = Long_val (index );
@@ -74,6 +98,12 @@ CAMLprim value caml_string_set(value str, value index, value newval)
7498 return Val_unit ;
7599}
76100
101+ CAMLprim value caml_bytes_set (value str , value index , value newval )
102+ {
103+ return caml_string_set (str ,index ,newval );
104+ }
105+
106+
77107CAMLprim value caml_string_get16 (value str , value index )
78108{
79109 intnat res ;
@@ -231,11 +261,21 @@ CAMLprim value caml_string_equal(value s1, value s2)
231261 return Val_true ;
232262}
233263
264+ CAMLprim value caml_bytes_equal (value s1 , value s2 )
265+ {
266+ return caml_string_equal (s1 ,s2 );
267+ }
268+
234269CAMLprim value caml_string_notequal (value s1 , value s2 )
235270{
236271 return Val_not (caml_string_equal (s1 , s2 ));
237272}
238273
274+ CAMLprim value caml_bytes_notequal (value s1 , value s2 )
275+ {
276+ return caml_string_notequal (s1 ,s2 );
277+ }
278+
239279CAMLprim value caml_string_compare (value s1 , value s2 )
240280{
241281 mlsize_t len1 , len2 ;
@@ -252,39 +292,81 @@ CAMLprim value caml_string_compare(value s1, value s2)
252292 return Val_int (0 );
253293}
254294
295+ CAMLprim value caml_bytes_compare (value s1 , value s2 )
296+ {
297+ return caml_string_compare (s1 ,s2 );
298+ }
299+
255300CAMLprim value caml_string_lessthan (value s1 , value s2 )
256301{
257302 return caml_string_compare (s1 , s2 ) < Val_int (0 ) ? Val_true : Val_false ;
258303}
259304
305+ CAMLprim value caml_bytes_lessthan (value s1 , value s2 )
306+ {
307+ return caml_string_lessthan (s1 ,s2 );
308+ }
309+
310+
260311CAMLprim value caml_string_lessequal (value s1 , value s2 )
261312{
262313 return caml_string_compare (s1 , s2 ) <= Val_int (0 ) ? Val_true : Val_false ;
263314}
264315
316+ CAMLprim value caml_bytes_lessequal (value s1 , value s2 )
317+ {
318+ return caml_string_lessequal (s1 ,s2 );
319+ }
320+
321+
265322CAMLprim value caml_string_greaterthan (value s1 , value s2 )
266323{
267324 return caml_string_compare (s1 , s2 ) > Val_int (0 ) ? Val_true : Val_false ;
268325}
269326
327+ CAMLprim value caml_bytes_greaterthan (value s1 , value s2 )
328+ {
329+ return caml_string_greaterthan (s1 ,s2 );
330+ }
331+
270332CAMLprim value caml_string_greaterequal (value s1 , value s2 )
271333{
272334 return caml_string_compare (s1 , s2 ) >= Val_int (0 ) ? Val_true : Val_false ;
273335}
274336
337+ CAMLprim value caml_bytes_greaterequal (value s1 , value s2 )
338+ {
339+ return caml_string_greaterequal (s1 ,s2 );
340+ }
341+
275342CAMLprim value caml_blit_string (value s1 , value ofs1 , value s2 , value ofs2 ,
276343 value n )
277344{
278345 memmove (& Byte (s2 , Long_val (ofs2 )), & Byte (s1 , Long_val (ofs1 )), Long_val (n ));
279346 return Val_unit ;
280347}
281348
349+ CAMLprim value caml_blit_bytes (value s1 , value ofs1 , value s2 , value ofs2 ,
350+ value n )
351+ {
352+ memmove (& Byte (s2 , Long_val (ofs2 )), & Byte (s1 , Long_val (ofs1 )), Long_val (n ));
353+ return Val_unit ;
354+ }
355+ /**
356+ * [caml_fill_string] is deprecated, use [caml_fill_bytes] instead
357+ */
282358CAMLprim value caml_fill_string (value s , value offset , value len , value init )
283359{
284360 memset (& Byte (s , Long_val (offset )), Int_val (init ), Long_val (len ));
285361 return Val_unit ;
286362}
287363
364+ CAMLprim value caml_fill_bytes (value s , value offset , value len , value init )
365+ {
366+ memset (& Byte (s , Long_val (offset )), Int_val (init ), Long_val (len ));
367+ return Val_unit ;
368+ }
369+
288370CAMLprim value caml_bitvect_test (value bv , value n )
289371{
290372 intnat pos = Long_val (n );
0 commit comments