1999-02-16 01:07:26 -08:00
|
|
|
|
(***********************************************************************)
|
|
|
|
|
(* *)
|
|
|
|
|
(* Objective Caml *)
|
|
|
|
|
(* *)
|
1999-02-25 02:26:38 -08:00
|
|
|
|
(* Pierre Weis and Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
1999-02-16 01:07:26 -08:00
|
|
|
|
(* *)
|
|
|
|
|
(* Copyright 1999 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1999-02-16 01:07:26 -08:00
|
|
|
|
(* *)
|
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
2004-04-14 04:37:53 -07:00
|
|
|
|
(* $Id$ *)
|
|
|
|
|
|
1999-02-16 01:07:26 -08:00
|
|
|
|
(* Extensible buffers *)
|
|
|
|
|
|
|
|
|
|
type t =
|
|
|
|
|
{mutable buffer : string;
|
|
|
|
|
mutable position : int;
|
|
|
|
|
mutable length : int;
|
1999-02-25 02:26:38 -08:00
|
|
|
|
initial_buffer : string}
|
1999-02-16 01:07:26 -08:00
|
|
|
|
|
1999-02-23 11:05:08 -08:00
|
|
|
|
let create n =
|
1999-10-02 05:09:43 -07:00
|
|
|
|
let n = if n < 1 then 1 else n in
|
|
|
|
|
let n = if n > Sys.max_string_length then Sys.max_string_length else n in
|
1999-02-23 11:05:08 -08:00
|
|
|
|
let s = String.create n in
|
2001-10-28 06:20:27 -08:00
|
|
|
|
{buffer = s; position = 0; length = n; initial_buffer = s}
|
1999-02-16 01:07:26 -08:00
|
|
|
|
|
1999-02-25 02:26:38 -08:00
|
|
|
|
let contents b = String.sub b.buffer 0 b.position
|
1999-02-16 01:07:26 -08:00
|
|
|
|
|
2004-04-14 04:26:21 -07:00
|
|
|
|
let sub b ofs len =
|
2005-10-25 11:34:07 -07:00
|
|
|
|
if ofs < 0 || len < 0 || ofs > b.position - len
|
2004-04-14 04:26:21 -07:00
|
|
|
|
then invalid_arg "Buffer.sub"
|
|
|
|
|
else begin
|
|
|
|
|
let r = String.create len in
|
|
|
|
|
String.blit b.buffer ofs r 0 len;
|
|
|
|
|
r
|
|
|
|
|
end
|
|
|
|
|
;;
|
|
|
|
|
|
2010-01-20 08:26:46 -08:00
|
|
|
|
let blit src srcoff dst dstoff len =
|
|
|
|
|
if len < 0 || srcoff < 0 || srcoff > src.position - len
|
|
|
|
|
|| dstoff < 0 || dstoff > (String.length dst) - len
|
|
|
|
|
then invalid_arg "Buffer.blit"
|
|
|
|
|
else
|
|
|
|
|
String.blit src.buffer srcoff dst dstoff len
|
|
|
|
|
;;
|
|
|
|
|
|
2005-10-25 11:34:07 -07:00
|
|
|
|
let nth b ofs =
|
|
|
|
|
if ofs < 0 || ofs >= b.position then
|
2004-04-14 04:26:21 -07:00
|
|
|
|
invalid_arg "Buffer.nth"
|
|
|
|
|
else String.get b.buffer ofs
|
|
|
|
|
;;
|
|
|
|
|
|
1999-02-25 02:26:38 -08:00
|
|
|
|
let length b = b.position
|
1999-02-23 11:05:08 -08:00
|
|
|
|
|
1999-02-25 02:26:38 -08:00
|
|
|
|
let clear b = b.position <- 0
|
1999-02-16 01:07:26 -08:00
|
|
|
|
|
1999-03-02 06:49:12 -08:00
|
|
|
|
let reset b =
|
|
|
|
|
b.position <- 0; b.buffer <- b.initial_buffer;
|
|
|
|
|
b.length <- String.length b.buffer
|
1999-02-16 01:07:26 -08:00
|
|
|
|
|
|
|
|
|
let resize b more =
|
1999-02-25 02:26:38 -08:00
|
|
|
|
let len = b.length in
|
|
|
|
|
let new_len = ref len in
|
|
|
|
|
while b.position + more > !new_len do new_len := 2 * !new_len done;
|
2002-03-29 06:24:22 -08:00
|
|
|
|
if !new_len > Sys.max_string_length then begin
|
|
|
|
|
if b.position + more <= Sys.max_string_length
|
|
|
|
|
then new_len := Sys.max_string_length
|
|
|
|
|
else failwith "Buffer.add: cannot grow buffer"
|
|
|
|
|
end;
|
1999-02-25 02:26:38 -08:00
|
|
|
|
let new_buffer = String.create !new_len in
|
1999-02-16 01:07:26 -08:00
|
|
|
|
String.blit b.buffer 0 new_buffer 0 b.position;
|
|
|
|
|
b.buffer <- new_buffer;
|
1999-02-25 02:26:38 -08:00
|
|
|
|
b.length <- !new_len
|
|
|
|
|
|
|
|
|
|
let add_char b c =
|
|
|
|
|
let pos = b.position in
|
|
|
|
|
if pos >= b.length then resize b 1;
|
|
|
|
|
b.buffer.[pos] <- c;
|
|
|
|
|
b.position <- pos + 1
|
|
|
|
|
|
|
|
|
|
let add_substring b s offset len =
|
2002-07-12 02:47:54 -07:00
|
|
|
|
if offset < 0 || len < 0 || offset > String.length s - len
|
1999-02-25 02:26:38 -08:00
|
|
|
|
then invalid_arg "Buffer.add_substring";
|
|
|
|
|
let new_position = b.position + len in
|
|
|
|
|
if new_position > b.length then resize b len;
|
|
|
|
|
String.blit s offset b.buffer b.position len;
|
|
|
|
|
b.position <- new_position
|
|
|
|
|
|
|
|
|
|
let add_string b s =
|
|
|
|
|
let len = String.length s in
|
|
|
|
|
let new_position = b.position + len in
|
|
|
|
|
if new_position > b.length then resize b len;
|
|
|
|
|
String.blit s 0 b.buffer b.position len;
|
|
|
|
|
b.position <- new_position
|
2005-10-25 11:34:07 -07:00
|
|
|
|
|
1999-02-25 02:26:38 -08:00
|
|
|
|
let add_buffer b bs =
|
|
|
|
|
add_substring b bs.buffer 0 bs.position
|
|
|
|
|
|
|
|
|
|
let add_channel b ic len =
|
2010-03-28 01:16:45 -07:00
|
|
|
|
if len < 0 || len > Sys.max_string_length then (* PR#5004 *)
|
|
|
|
|
invalid_arg "Buffer.add_channel";
|
1999-02-25 02:26:38 -08:00
|
|
|
|
if b.position + len > b.length then resize b len;
|
|
|
|
|
really_input ic b.buffer b.position len;
|
|
|
|
|
b.position <- b.position + len
|
|
|
|
|
|
|
|
|
|
let output_buffer oc b =
|
|
|
|
|
output oc b.buffer 0 b.position
|
2003-04-28 01:13:20 -07:00
|
|
|
|
|
|
|
|
|
let closing = function
|
|
|
|
|
| '(' -> ')'
|
|
|
|
|
| '{' -> '}'
|
|
|
|
|
| _ -> assert false;;
|
|
|
|
|
|
|
|
|
|
(* opening and closing: open and close characters, typically ( and )
|
2004-06-14 13:20:16 -07:00
|
|
|
|
k: balance of opening and closing chars
|
|
|
|
|
s: the string where we are searching
|
|
|
|
|
start: the index where we start the search. *)
|
2003-04-28 01:13:20 -07:00
|
|
|
|
let advance_to_closing opening closing k s start =
|
|
|
|
|
let rec advance k i lim =
|
|
|
|
|
if i >= lim then raise Not_found else
|
|
|
|
|
if s.[i] = opening then advance (k + 1) (i + 1) lim else
|
|
|
|
|
if s.[i] = closing then
|
|
|
|
|
if k = 0 then i else advance (k - 1) (i + 1) lim
|
|
|
|
|
else advance k (i + 1) lim in
|
|
|
|
|
advance k start (String.length s);;
|
|
|
|
|
|
|
|
|
|
let advance_to_non_alpha s start =
|
|
|
|
|
let rec advance i lim =
|
|
|
|
|
if i >= lim then lim else
|
|
|
|
|
match s.[i] with
|
|
|
|
|
| 'a' .. 'z' | 'A' .. 'Z' | '0' .. '9' | '_' |
|
2005-10-25 11:34:07 -07:00
|
|
|
|
'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|
|
|
|
|
|
'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|
|
|
|
|
|
'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|
|
|
|
|
|
'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>'|'<27>' ->
|
2008-09-09 01:50:39 -07:00
|
|
|
|
advance (i + 1) lim
|
2003-04-28 01:13:20 -07:00
|
|
|
|
| _ -> i in
|
|
|
|
|
advance start (String.length s);;
|
|
|
|
|
|
2004-06-14 13:20:16 -07:00
|
|
|
|
(* We are just at the beginning of an ident in s, starting at start. *)
|
2008-09-09 01:50:39 -07:00
|
|
|
|
let find_ident s start lim =
|
|
|
|
|
if start >= lim then raise Not_found else
|
2003-04-28 01:13:20 -07:00
|
|
|
|
match s.[start] with
|
|
|
|
|
(* Parenthesized ident ? *)
|
|
|
|
|
| '(' | '{' as c ->
|
|
|
|
|
let new_start = start + 1 in
|
|
|
|
|
let stop = advance_to_closing c (closing c) 0 s new_start in
|
|
|
|
|
String.sub s new_start (stop - start - 1), stop + 1
|
|
|
|
|
(* Regular ident *)
|
|
|
|
|
| _ ->
|
|
|
|
|
let stop = advance_to_non_alpha s (start + 1) in
|
|
|
|
|
String.sub s start (stop - start), stop;;
|
|
|
|
|
|
2003-05-14 10:52:40 -07:00
|
|
|
|
(* Substitute $ident, $(ident), or ${ident} in s,
|
|
|
|
|
according to the function mapping f. *)
|
2003-04-28 01:13:20 -07:00
|
|
|
|
let add_substitute b f s =
|
|
|
|
|
let lim = String.length s in
|
|
|
|
|
let rec subst previous i =
|
|
|
|
|
if i < lim then begin
|
|
|
|
|
match s.[i] with
|
|
|
|
|
| '$' as current when previous = '\\' ->
|
|
|
|
|
add_char b current;
|
2008-09-09 01:50:39 -07:00
|
|
|
|
subst ' ' (i + 1)
|
2003-04-28 01:13:20 -07:00
|
|
|
|
| '$' ->
|
2008-09-09 01:50:39 -07:00
|
|
|
|
let j = i + 1 in
|
|
|
|
|
let ident, next_i = find_ident s j lim in
|
2003-04-28 01:13:20 -07:00
|
|
|
|
add_string b (f ident);
|
|
|
|
|
subst ' ' next_i
|
|
|
|
|
| current when previous == '\\' ->
|
|
|
|
|
add_char b '\\';
|
|
|
|
|
add_char b current;
|
2008-09-09 01:50:39 -07:00
|
|
|
|
subst ' ' (i + 1)
|
2003-04-28 01:13:20 -07:00
|
|
|
|
| '\\' as current ->
|
|
|
|
|
subst current (i + 1)
|
|
|
|
|
| current ->
|
|
|
|
|
add_char b current;
|
|
|
|
|
subst current (i + 1)
|
2008-09-09 01:50:39 -07:00
|
|
|
|
end else
|
|
|
|
|
if previous = '\\' then add_char b previous in
|
2003-04-28 01:13:20 -07:00
|
|
|
|
subst ' ' 0;;
|