Added shared library support for NetBSD and OpenBSD.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8394 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2007-08-23 07:43:06 +00:00
parent 45bef8fffc
commit 8e5fb9bb75
5 changed files with 38 additions and 26 deletions

Binary file not shown.

Binary file not shown.

2
configure vendored
View File

@ -488,7 +488,7 @@ mksharedlibrpath=''
if test $withsharedlibs = "yes"; then
case "$host" in
*-*-linux-gnu|*-*-linux|*-*-freebsd[3-9]*|*-*-gnu*)
*-*-linux-gnu|*-*-linux|*-*-freebsd[3-9]*|*-*-openbsd[3-9]*|*-*-netbsd[3-9]*|*-*-gnu*)
sharedcccompopts="-fPIC"
mksharedlib="$bytecc -shared -o"
bytecclinkopts="$bytecclinkopts -Wl,-E"

View File

@ -36,7 +36,7 @@ val invalidate_current_char : scanbuf -> unit;;
val peek_char : scanbuf -> char;;
(* [Scanning.peek_char ib] returns the current char available in
the buffer or read one if necessary (when the current character is
the buffer or reads one if necessary (when the current character is
already scanned).
If no character can be read, sets an end of file condition and
returns '\000'. *)
@ -134,7 +134,7 @@ let next_char ib =
ib.current_char <- c;
ib.current_char_is_valid <- true;
ib.char_count <- succ ib.char_count;
if c == '\n' then ib.line_count <- succ ib.line_count;
if c = '\n' then ib.line_count <- succ ib.line_count;
c with
| End_of_file ->
let c = null_char in
@ -611,7 +611,7 @@ let scan_string stp max ib =
if max = 0 then max else
let c = Scanning.peek_char ib in
if Scanning.eof ib then max else
if stp == [] then
if stp = [] then
match c with
| ' ' | '\t' | '\n' | '\r' -> max
| c -> loop (Scanning.store_char ib c max) else
@ -974,22 +974,27 @@ let list_iter_i f l =
If the scanning or some conversion fails, the main scanning function
aborts and applies the scanning buffer and a string that explains
the error to the error handling function [ef] (the error continuation). *)
let ascanf sc fmt =
let ac = Tformat.ac_of_format fmt in
match ac.Tformat.ac_rdrs with
| 0 -> Obj.magic (fun f -> sc fmt [||] f)
| 1 -> Obj.magic (fun x f -> sc fmt [| Obj.repr x |] f)
| 2 -> Obj.magic (fun x y f -> sc fmt [| Obj.repr x; Obj.repr y; |] f)
| 3 -> Obj.magic (fun x y z f ->
sc fmt [| Obj.repr x; Obj.repr y; Obj.repr z; |] f)
| nargs ->
let rec loop i args =
if i >= nargs then
let a = Array.make nargs (Obj.repr 0) in
list_iter_i (fun i arg -> a.(nargs - i - 1) <- arg) args;
Obj.magic (fun f -> sc fmt a f)
else Obj.magic (fun x -> loop (succ i) (x :: args)) in
loop 0 [];;
match ac.Tformat.ac_rdrs with
| 0 ->
Obj.magic (fun f -> sc fmt [||] f)
| 1 ->
Obj.magic (fun x f -> sc fmt [| Obj.repr x |] f)
| 2 ->
Obj.magic (fun x y f -> sc fmt [| Obj.repr x; Obj.repr y; |] f)
| 3 ->
Obj.magic
(fun x y z f -> sc fmt [| Obj.repr x; Obj.repr y; Obj.repr z; |] f)
| nargs ->
let rec loop i args =
if i >= nargs then
let a = Array.make nargs (Obj.repr 0) in
list_iter_i (fun i arg -> a.(nargs - i - 1) <- arg) args;
Obj.magic (fun f -> sc fmt a f)
else Obj.magic (fun x -> loop (succ i) (x :: args)) in
loop 0 [];;
let scan_format ib ef fmt v f =
@ -1106,8 +1111,11 @@ let scan_format ib ef fmt v f =
let rf = token_string ib in
if not (compatible_format_type rf mf) then format_mismatch rf mf ib else
if conv = '{' (* '}' *) then scan_fmt ir (stack f rf) j else
let nf = scan_fmt ir (Obj.magic rf) 0 in
scan_fmt ir (stack f nf) j
(* try scan_fmt 0 (fun () -> f) 0 with*)
scan_fmt ir (stack (stack f rf) nf) j
| c -> bad_conversion fmt i c
and scan_fmt_stoppers i =

View File

@ -129,7 +129,7 @@ type ('a, 'b, 'c, 'd) scanner =
according to some format string; more precisely, if [scan] is some
formatted input function, then [scan ib fmt f] applies [f] to the arguments
specified by the format string [fmt], when [scan] has read those arguments
from scanning buffer [ib].
from the scanning buffer [ib].
For instance, the [scanf] function below has type [('a, 'b, 'c, 'd)
scanner], since it is a formatted input function that reads from [stdib]:
@ -229,15 +229,19 @@ val bscanf : Scanning.scanbuf -> ('a, 'b, 'c, 'd) scanner;;
applies it to the scanning buffer [ib] to read the next argument. The
input function [ri] must therefore have type [Scanning.scanbuf -> 'a] and
the argument read has type ['a].
- [\{ fmt %\}]: reads a format string argument to the format
specified by the internal format [fmt]. The format string to be
read must have the same type as the internal format [fmt].
For instance, "%\{%i%\}" reads any format string that can read a value of
- [\{ fmt %\}]: reads a format string argument.
The format string read must have the same type as [fmt].
For instance, ["%\{%i%\}"] reads any format string that can read a value of
type [int]; hence [Scanf.sscanf "fmt:\\\"number is %u\\\"" "fmt:%\{%i%\}"]
succeeds and returns the format string ["number is %u"].
- [\( fmt %\)]: scanning format substitution.
Reads a format string to replace [fmt]. The format string read
must have the same type as [fmt].
Reads a format string to replace [fmt].
The format string read must have the same type as [fmt].
For instance, ["%\( %i% \)"] reads any format string that can read a value
of type [int]; hence [Scanf.sscanf "\\\"%4d\\\"1234.00" "%\(%i%\)"]
succeeds and returns the format string ["number is %u"].
(** Must do something about that doc! *)
- [l]: returns the number of lines read so far.
- [n]: returns the number of characters read so far.
- [N] or [L]: returns the number of tokens read so far.