summaryrefslogtreecommitdiffstats
path: root/otherlibs
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2002-11-01 17:06:47 +0000
committerDamien Doligez <damien.doligez-inria.fr>2002-11-01 17:06:47 +0000
commited3123ee870f0362a576a88e0c7cf266581ee1b4 (patch)
treecf48c20af4544b2be26740666dffbc1ed4b6e380 /otherlibs
parent24b167171c95abd67eb787ea2cd5aff655ba4574 (diff)
changement des locations, premiere tranche
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5224 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs')
-rw-r--r--otherlibs/bigarray/.depend20
-rw-r--r--otherlibs/graph/.depend83
-rw-r--r--otherlibs/labltk/browser/lexical.ml2
-rw-r--r--otherlibs/labltk/browser/searchid.ml49
-rw-r--r--otherlibs/labltk/browser/searchpos.ml15
-rw-r--r--otherlibs/labltk/browser/typecheck.ml39
-rw-r--r--otherlibs/labltk/camltk/.depend62
-rw-r--r--otherlibs/labltk/labltk/.depend30
-rw-r--r--otherlibs/num/.depend12
-rw-r--r--otherlibs/str/.depend7
-rw-r--r--otherlibs/threads/.depend19
-rw-r--r--otherlibs/unix/.depend366
12 files changed, 486 insertions, 218 deletions
diff --git a/otherlibs/bigarray/.depend b/otherlibs/bigarray/.depend
index fde04c9d2..7c4e124ea 100644
--- a/otherlibs/bigarray/.depend
+++ b/otherlibs/bigarray/.depend
@@ -1,17 +1,17 @@
-bigarray_stubs.o : ../../byterun/alloc.h ../../byterun/misc.h \
- ../../byterun/config.h ../../byterun/../config/m.h \
- ../../byterun/../config/s.h ../../byterun/mlvalues.h bigarray.h \
+bigarray_stubs.o: bigarray_stubs.c ../../byterun/alloc.h \
+ ../../byterun/misc.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/mlvalues.h bigarray.h \
../../byterun/custom.h ../../byterun/fail.h ../../byterun/intext.h \
../../byterun/io.h ../../byterun/fix_code.h ../../byterun/memory.h \
../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
- ../../byterun/minor_gc.h
-mmap_unix.o : bigarray.h ../../byterun/mlvalues.h ../../byterun/config.h \
- ../../byterun/../config/m.h ../../byterun/../config/s.h \
+ ../../byterun/minor_gc.h
+mmap_unix.o: mmap_unix.c bigarray.h ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h ../../byterun/custom.h ../../byterun/fail.h \
- ../../byterun/sys.h
-mmap_win32.o : bigarray.h ../../byterun/mlvalues.h ../../byterun/config.h \
- ../../byterun/../config/m.h ../../byterun/../config/s.h \
+ ../../byterun/sys.h
+mmap_win32.o: mmap_win32.c bigarray.h ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h ../../byterun/alloc.h ../../byterun/custom.h \
- ../../byterun/fail.h ../../byterun/sys.h ../unix/unixsupport.h
+ ../../byterun/fail.h ../../byterun/sys.h ../unix/unixsupport.h
bigarray.cmo: bigarray.cmi
bigarray.cmx: bigarray.cmi
diff --git a/otherlibs/graph/.depend b/otherlibs/graph/.depend
index c0b0f54e0..70ab5db6f 100644
--- a/otherlibs/graph/.depend
+++ b/otherlibs/graph/.depend
@@ -1,15 +1,74 @@
-color.o: color.c libgraph.h
-draw.o: draw.c libgraph.h
-dump_img.o: dump_img.c libgraph.h image.h
-events.o: events.c libgraph.h
-fill.o: fill.c libgraph.h
-image.o: image.c libgraph.h image.h
-make_img.o: make_img.c libgraph.h image.h
-open.o: open.c libgraph.h
-point_col.o: point_col.c libgraph.h
-sound.o: sound.c libgraph.h
-subwindow.o: subwindow.c libgraph.h
-text.o: text.c libgraph.h
+color.o: color.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h /usr/X11R6/include/X11/Xatom.h
+draw.o: draw.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h ../../byterun/alloc.h
+dump_img.o: dump_img.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h image.h ../../byterun/alloc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h
+events.o: events.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h ../../byterun/alloc.h \
+ ../../byterun/signals.h
+fill.o: fill.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h ../../byterun/memory.h \
+ ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h
+image.o: image.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h image.h ../../byterun/alloc.h \
+ ../../byterun/custom.h
+make_img.o: make_img.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h image.h ../../byterun/memory.h \
+ ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h
+open.o: open.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h ../../byterun/alloc.h \
+ ../../byterun/callback.h ../../byterun/fail.h ../../byterun/memory.h \
+ ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h
+point_col.o: point_col.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h
+sound.o: sound.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h
+subwindow.o: subwindow.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h
+text.o: text.c libgraph.h /usr/X11R6/include/X11/Xlib.h \
+ /usr/X11R6/include/X11/X.h /usr/X11R6/include/X11/Xfuncproto.h \
+ /usr/X11R6/include/X11/Xosdefs.h /usr/X11R6/include/X11/Xutil.h \
+ ../../byterun/mlvalues.h ../../byterun/config.h ../../config/m.h \
+ ../../config/s.h ../../byterun/misc.h ../../byterun/alloc.h
graphics.cmo: graphics.cmi
graphics.cmx: graphics.cmi
graphicsX11.cmo: graphics.cmi graphicsX11.cmi
diff --git a/otherlibs/labltk/browser/lexical.ml b/otherlibs/labltk/browser/lexical.ml
index c4bd3b1f5..a2573ef7c 100644
--- a/otherlibs/labltk/browser/lexical.ml
+++ b/otherlibs/labltk/browser/lexical.ml
@@ -140,4 +140,4 @@ let tag ?(start=tstart) ?(stop=tend) tw =
done
with
End_of_file -> ()
- | Lexer.Error (err, s, e) -> ()
+ | Lexer.Error (err, loc) -> ()
diff --git a/otherlibs/labltk/browser/searchid.ml b/otherlibs/labltk/browser/searchid.ml
index 8863e6d03..65cbaa8bd 100644
--- a/otherlibs/labltk/browser/searchid.ml
+++ b/otherlibs/labltk/browser/searchid.ml
@@ -288,18 +288,31 @@ let search_string_type text ~mode =
end in
try Typemod.transl_signature env sexp
with Env.Error err -> []
- | Typemod.Error (l,_) -> raise (Error (l.loc_start - 8, l.loc_end - 8))
- | Typetexp.Error (l,_) -> raise (Error (l.loc_start - 8, l.loc_end - 8))
+ | Typemod.Error (l,_) ->
+ let start_c = l.loc_start.Lexing.pos_cnum in
+ let end_c = l.loc_end.Lexing.pos_cnum in
+ raise (Error (start_c - 8, end_c - 8))
+ | Typetexp.Error (l,_) ->
+ let start_c = l.loc_start.Lexing.pos_cnum in
+ let end_c = l.loc_end.Lexing.pos_cnum in
+ raise (Error (start_c - 8, end_c - 8))
in match sign with
[Tsig_value (_, vd)] ->
search_all_types vd.val_type ~mode
| _ -> []
with
Syntaxerr.Error(Syntaxerr.Unclosed(l,_,_,_)) ->
- raise (Error (l.loc_start - 8, l.loc_end - 8))
+ let start_c = l.loc_start.Lexing.pos_cnum in
+ let end_c = l.loc_end.Lexing.pos_cnum in
+ raise (Error (start_c - 8, end_c - 8))
| Syntaxerr.Error(Syntaxerr.Other l) ->
- raise (Error (l.loc_start - 8, l.loc_end - 8))
- | Lexer.Error (_, s, e) -> raise (Error (s - 8, e - 8))
+ let start_c = l.loc_start.Lexing.pos_cnum in
+ let end_c = l.loc_end.Lexing.pos_cnum in
+ raise (Error (start_c - 8, end_c - 8))
+ | Lexer.Error (_, l) ->
+ let start_c = l.loc_start.Lexing.pos_cnum in
+ let end_c = l.loc_end.Lexing.pos_cnum in
+ raise (Error (start_c - 8, end_c - 8))
let longident_of_string text =
let exploded = ref [] and l = ref 0 in
@@ -419,7 +432,7 @@ let search_structure str ~name ~kind ~prefix =
begin fun acc item ->
match item.pstr_desc with
Pstr_module (s, mexp) when s = modu ->
- loc := mexp.pmod_loc.loc_start;
+ loc := mexp.pmod_loc.loc_start.Lexing.pos_cnum;
begin match mexp.pmod_desc with
Pmod_structure str -> str
| _ -> []
@@ -435,14 +448,14 @@ let search_structure str ~name ~kind ~prefix =
List.iter l ~f:
begin fun (pat,_) ->
if List.mem name (bound_variables pat)
- then loc := pat.ppat_loc.loc_start
+ then loc := pat.ppat_loc.loc_start.Lexing.pos_cnum
end;
false
| Pstr_primitive (s, _) when kind = Pvalue -> name = s
| Pstr_type l when kind = Ptype ->
List.iter l ~f:
begin fun (s, td) ->
- if s = name then loc := td.ptype_loc.loc_start
+ if s = name then loc := td.ptype_loc.loc_start.Lexing.pos_cnum
end;
false
| Pstr_exception (s, _) when kind = Pconstructor -> name = s
@@ -451,17 +464,19 @@ let search_structure str ~name ~kind ~prefix =
| Pstr_class l when kind = Pclass || kind = Ptype || kind = Pcltype ->
List.iter l ~f:
begin fun c ->
- if c.pci_name = name then loc := c.pci_loc.loc_start
+ if c.pci_name = name
+ then loc := c.pci_loc.loc_start.Lexing.pos_cnum
end;
false
| Pstr_class_type l when kind = Pcltype || kind = Ptype ->
List.iter l ~f:
begin fun c ->
- if c.pci_name = name then loc := c.pci_loc.loc_start
+ if c.pci_name = name
+ then loc := c.pci_loc.loc_start.Lexing.pos_cnum
end;
false
| _ -> false
- then loc := item.pstr_loc.loc_start
+ then loc := item.pstr_loc.loc_start.Lexing.pos_cnum
end;
!loc
@@ -475,7 +490,7 @@ let search_signature sign ~name ~kind ~prefix =
begin fun acc item ->
match item.psig_desc with
Psig_module (s, mtyp) when s = modu ->
- loc := mtyp.pmty_loc.loc_start;
+ loc := mtyp.pmty_loc.loc_start.Lexing.pos_cnum;
begin match mtyp.pmty_desc with
Pmty_signature sign -> sign
| _ -> []
@@ -491,7 +506,7 @@ let search_signature sign ~name ~kind ~prefix =
| Psig_type l when kind = Ptype ->
List.iter l ~f:
begin fun (s, td) ->
- if s = name then loc := td.ptype_loc.loc_start
+ if s = name then loc := td.ptype_loc.loc_start.Lexing.pos_cnum
end;
false
| Psig_exception (s, _) when kind = Pconstructor -> name = s
@@ -500,16 +515,18 @@ let search_signature sign ~name ~kind ~prefix =
| Psig_class l when kind = Pclass || kind = Ptype || kind = Pcltype ->
List.iter l ~f:
begin fun c ->
- if c.pci_name = name then loc := c.pci_loc.loc_start
+ if c.pci_name = name
+ then loc := c.pci_loc.loc_start.Lexing.pos_cnum
end;
false
| Psig_class_type l when kind = Ptype || kind = Pcltype ->
List.iter l ~f:
begin fun c ->
- if c.pci_name = name then loc := c.pci_loc.loc_start
+ if c.pci_name = name
+ then loc := c.pci_loc.loc_start.Lexing.pos_cnum
end;
false
| _ -> false
- then loc := item.psig_loc.loc_start
+ then loc := item.psig_loc.loc_start.Lexing.pos_cnum
end;
!loc
diff --git a/otherlibs/labltk/browser/searchpos.ml b/otherlibs/labltk/browser/searchpos.ml
index 03e930c7e..680bb8ff0 100644
--- a/otherlibs/labltk/browser/searchpos.ml
+++ b/otherlibs/labltk/browser/searchpos.ml
@@ -39,11 +39,12 @@ let lines_to_chars n ~text:s =
in ltc n ~pos:0
let in_loc loc ~pos =
- loc.loc_ghost || pos >= loc.loc_start && pos < loc.loc_end
+ loc.loc_ghost || pos >= loc.loc_start.Lexing.pos_cnum
+ && pos < loc.loc_end.Lexing.pos_cnum
let le_loc loc1 loc2 =
- loc1.loc_start <= loc2.loc_start
- && loc1.loc_end >= loc2.loc_end
+ loc1.loc_start.Lexing.pos_cnum <= loc2.loc_start.Lexing.pos_cnum
+ && loc1.loc_end.Lexing.pos_cnum >= loc2.loc_end.Lexing.pos_cnum
let add_found ~found sol ~env ~loc =
if loc.loc_ghost then () else
@@ -390,9 +391,11 @@ let rec view_signature ?title ?path ?(env = !start_env) ?(detach=false) sign =
Syntaxerr.Unclosed(l,_,_,_) -> l
| Syntaxerr.Other l -> l
in
- Jg_text.tag_and_see tw ~start:(tpos l.loc_start)
- ~stop:(tpos l.loc_end) ~tag:"error"; []
- | Lexer.Error (_, s, e) ->
+ Jg_text.tag_and_see tw ~start:(tpos l.loc_start.Lexing.pos_cnum)
+ ~stop:(tpos l.loc_end.Lexing.pos_cnum) ~tag:"error"; []
+ | Lexer.Error (_, l) ->
+ let s = l.loc_start.Lexing.pos_cnum in
+ let e = l.loc_end.Lexing.pos_cnum in
Jg_text.tag_and_see tw ~start:(tpos s) ~stop:(tpos e) ~tag:"error"; []
in
Jg_bind.enter_focus tw;
diff --git a/otherlibs/labltk/browser/typecheck.ml b/otherlibs/labltk/browser/typecheck.ml
index 3a7f66672..b8106205d 100644
--- a/otherlibs/labltk/browser/typecheck.ml
+++ b/otherlibs/labltk/browser/typecheck.ml
@@ -121,40 +121,39 @@ let f txt =
| Env.Error _ | Ctype.Tags _ | Failure _ as exn ->
let et, ew, end_message = Jg_message.formatted ~title:"Error !" () in
error_messages := et :: !error_messages;
- let s, e = match exn with
- Lexer.Error (err, s, e) ->
- Lexer.report_error Format.std_formatter err; s,e
+ let range = match exn with
+ Lexer.Error (err, l) ->
+ Lexer.report_error Format.std_formatter err; l
| Syntaxerr.Error err ->
Syntaxerr.report_error Format.std_formatter err;
- let l =
- match err with
- Syntaxerr.Unclosed(l,_,_,_) -> l
- | Syntaxerr.Other l -> l
- in l.loc_start, l.loc_end
+ begin match err with
+ Syntaxerr.Unclosed(l,_,_,_) -> l
+ | Syntaxerr.Other l -> l
+ end
| Typecore.Error (l,err) ->
- Typecore.report_error Format.std_formatter err;
- l.loc_start, l.loc_end
+ Typecore.report_error Format.std_formatter err; l
| Typeclass.Error (l,err) ->
- Typeclass.report_error Format.std_formatter err;
- l.loc_start, l.loc_end
+ Typeclass.report_error Format.std_formatter err; l
| Typedecl.Error (l, err) ->
- Typedecl.report_error Format.std_formatter err;
- l.loc_start, l.loc_end
+ Typedecl.report_error Format.std_formatter err; l
| Typemod.Error (l,err) ->
- Typemod.report_error Format.std_formatter err; l.loc_start, l.loc_end
+ Typemod.report_error Format.std_formatter err; l
| Typetexp.Error (l,err) ->
- Typetexp.report_error Format.std_formatter err; l.loc_start, l.loc_end
+ Typetexp.report_error Format.std_formatter err; l
| Includemod.Error errl ->
- Includemod.report_error Format.std_formatter errl; 0, 0
+ Includemod.report_error Format.std_formatter errl; Location.none
| Env.Error err ->
- Env.report_error Format.std_formatter err; 0, 0
+ Env.report_error Format.std_formatter err; Location.none
| Ctype.Tags(l, l') ->
- Format.printf "In this program,@ variant constructors@ `%s and `%s@ have same hash value.@." l l'; 0, 0
+ Format.printf "In this program,@ variant constructors@ `%s and `%s@ have same hash value.@." l l';
+ Location.none
| Failure s ->
- Format.printf "%s.@." s; 0, 0
+ Format.printf "%s.@." s; Location.none
| _ -> assert false
in
end_message ();
+ let s = range.loc_start.Lexing.pos_cnum in
+ let e = range.loc_end.Lexing.pos_cnum in
if s < e then
Jg_text.tag_and_see txt.tw ~start:(tpos s) ~stop:(tpos e) ~tag:"error"
end;
diff --git a/otherlibs/labltk/camltk/.depend b/otherlibs/labltk/camltk/.depend
index 6c4ac94bc..203fe291a 100644
--- a/otherlibs/labltk/camltk/.depend
+++ b/otherlibs/labltk/camltk/.depend
@@ -11,16 +11,16 @@ cFont.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cFrame.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cGrab.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cGrid.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
-cImagebitmap.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cImage.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
+cImagebitmap.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cImagephoto.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cLabel.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cListbox.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
-cMenubutton.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cMenu.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
+cMenubutton.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cMessage.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
-cOptionmenu.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cOption.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
+cOptionmenu.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cPack.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cPalette.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cPixmap.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
@@ -36,22 +36,6 @@ cTkwait.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cToplevel.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cWinfo.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
cWm.cmi: cTk.cmo ../support/textvariable.cmi ../support/widget.cmi
-camltk.cmo: cBell.cmi cButton.cmi cCanvas.cmi cCheckbutton.cmi cClipboard.cmi \
- cDialog.cmi cEncoding.cmi cEntry.cmi cFocus.cmi cFont.cmi cFrame.cmi \
- cGrab.cmi cGrid.cmi cImage.cmi cImagebitmap.cmi cImagephoto.cmi \
- cLabel.cmi cListbox.cmi cMenu.cmi cMenubutton.cmi cMessage.cmi \
- cOption.cmi cOptionmenu.cmi cPack.cmi cPalette.cmi cPixmap.cmi cPlace.cmi \
- cRadiobutton.cmi cResource.cmi cScale.cmi cScrollbar.cmi cSelection.cmi \
- cText.cmi cTk.cmo cTkvars.cmi cTkwait.cmi cToplevel.cmi cWinfo.cmi \
- cWm.cmi
-camltk.cmx: cBell.cmx cButton.cmx cCanvas.cmx cCheckbutton.cmx cClipboard.cmx \
- cDialog.cmx cEncoding.cmx cEntry.cmx cFocus.cmx cFont.cmx cFrame.cmx \
- cGrab.cmx cGrid.cmx cImage.cmx cImagebitmap.cmx cImagephoto.cmx \
- cLabel.cmx cListbox.cmx cMenu.cmx cMenubutton.cmx cMessage.cmx \
- cOption.cmx cOptionmenu.cmx cPack.cmx cPalette.cmx cPixmap.cmx cPlace.cmx \
- cRadiobutton.cmx cResource.cmx cScale.cmx cScrollbar.cmx cSelection.cmx \
- cText.cmx cTk.cmx cTkvars.cmx cTkwait.cmx cToplevel.cmx cWinfo.cmx \
- cWm.cmx
cBell.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cBell.cmi
cBell.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
@@ -104,14 +88,14 @@ cGrid.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cGrid.cmi
cGrid.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cGrid.cmi
-cImagebitmap.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
- ../support/widget.cmi cImagebitmap.cmi
-cImagebitmap.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
- ../support/widget.cmx cImagebitmap.cmi
cImage.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cImage.cmi
cImage.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cImage.cmi
+cImagebitmap.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
+ ../support/widget.cmi cImagebitmap.cmi
+cImagebitmap.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
+ ../support/widget.cmx cImagebitmap.cmi
cImagephoto.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cImagephoto.cmi
cImagephoto.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
@@ -124,26 +108,26 @@ cListbox.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cListbox.cmi
cListbox.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cListbox.cmi
-cMenubutton.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
- ../support/widget.cmi cMenubutton.cmi
-cMenubutton.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
- ../support/widget.cmx cMenubutton.cmi
cMenu.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cMenu.cmi
cMenu.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cMenu.cmi
+cMenubutton.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
+ ../support/widget.cmi cMenubutton.cmi
+cMenubutton.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
+ ../support/widget.cmx cMenubutton.cmi
cMessage.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cMessage.cmi
cMessage.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cMessage.cmi
-cOptionmenu.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
- ../support/widget.cmi cOptionmenu.cmi
-cOptionmenu.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
- ../support/widget.cmx cOptionmenu.cmi
cOption.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cOption.cmi
cOption.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cOption.cmi
+cOptionmenu.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
+ ../support/widget.cmi cOptionmenu.cmi
+cOptionmenu.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
+ ../support/widget.cmx cOptionmenu.cmi
cPack.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cPack.cmi
cPack.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
@@ -208,3 +192,19 @@ cWm.cmo: cTk.cmo ../support/protocol.cmi ../support/textvariable.cmi \
../support/widget.cmi cWm.cmi
cWm.cmx: cTk.cmx ../support/protocol.cmx ../support/textvariable.cmx \
../support/widget.cmx cWm.cmi
+camltk.cmo: cBell.cmi cButton.cmi cCanvas.cmi cCheckbutton.cmi cClipboard.cmi \
+ cDialog.cmi cEncoding.cmi cEntry.cmi cFocus.cmi cFont.cmi cFrame.cmi \
+ cGrab.cmi cGrid.cmi cImage.cmi cImagebitmap.cmi cImagephoto.cmi \
+ cLabel.cmi cListbox.cmi cMenu.cmi cMenubutton.cmi cMessage.cmi \
+ cOption.cmi cOptionmenu.cmi cPack.cmi cPalette.cmi cPixmap.cmi cPlace.cmi \
+ cRadiobutton.cmi cResource.cmi cScale.cmi cScrollbar.cmi cSelection.cmi \
+ cText.cmi cTk.cmo cTkvars.cmi cTkwait.cmi cToplevel.cmi cWinfo.cmi \
+ cWm.cmi
+camltk.cmx: cBell.cmx cButton.cmx cCanvas.cmx cCheckbutton.cmx cClipboard.cmx \
+ cDialog.cmx cEncoding.cmx cEntry.cmx cFocus.cmx cFont.cmx cFrame.cmx \
+ cGrab.cmx cGrid.cmx cImage.cmx cImagebitmap.cmx cImagephoto.cmx \
+ cLabel.cmx cListbox.cmx cMenu.cmx cMenubutton.cmx cMessage.cmx \
+ cOption.cmx cOptionmenu.cmx cPack.cmx cPalette.cmx cPixmap.cmx cPlace.cmx \
+ cRadiobutton.cmx cResource.cmx cScale.cmx cScrollbar.cmx cSelection.cmx \
+ cText.cmx cTk.cmx cTkvars.cmx cTkwait.cmx cToplevel.cmx cWinfo.cmx \
+ cWm.cmx
diff --git a/otherlibs/labltk/labltk/.depend b/otherlibs/labltk/labltk/.depend
index e3cd27cf1..f1273b18b 100644
--- a/otherlibs/labltk/labltk/.depend
+++ b/otherlibs/labltk/labltk/.depend
@@ -11,16 +11,16 @@ font.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
frame.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
grab.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
grid.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
-imagebitmap.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
image.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
+imagebitmap.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
imagephoto.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
label.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
listbox.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
-menubutton.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
menu.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
+menubutton.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
message.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
-optionmenu.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
option.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
+optionmenu.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
pack.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
palette.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
pixmap.cmi: ../support/textvariable.cmi tk.cmo ../support/widget.cmi
@@ -87,14 +87,14 @@ grid.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi grid.cmi
grid.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
../support/widget.cmx grid.cmi
-imagebitmap.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
- ../support/widget.cmi imagebitmap.cmi
-imagebitmap.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
- ../support/widget.cmx imagebitmap.cmi
image.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi image.cmi
image.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
../support/widget.cmx image.cmi
+imagebitmap.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
+ ../support/widget.cmi imagebitmap.cmi
+imagebitmap.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
+ ../support/widget.cmx imagebitmap.cmi
imagephoto.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi imagephoto.cmi
imagephoto.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
@@ -125,26 +125,26 @@ listbox.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi listbox.cmi
listbox.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
../support/widget.cmx listbox.cmi
-menubutton.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
- ../support/widget.cmi menubutton.cmi
-menubutton.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
- ../support/widget.cmx menubutton.cmi
menu.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi menu.cmi
menu.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
../support/widget.cmx menu.cmi
+menubutton.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
+ ../support/widget.cmi menubutton.cmi
+menubutton.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
+ ../support/widget.cmx menubutton.cmi
message.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi message.cmi
message.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
../support/widget.cmx message.cmi
-optionmenu.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
- ../support/widget.cmi optionmenu.cmi
-optionmenu.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
- ../support/widget.cmx optionmenu.cmi
option.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi option.cmi
option.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
../support/widget.cmx option.cmi
+optionmenu.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
+ ../support/widget.cmi optionmenu.cmi
+optionmenu.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
+ ../support/widget.cmx optionmenu.cmi
pack.cmo: ../support/protocol.cmi ../support/textvariable.cmi tk.cmo \
../support/widget.cmi pack.cmi
pack.cmx: ../support/protocol.cmx ../support/textvariable.cmx tk.cmx \
diff --git a/otherlibs/num/.depend b/otherlibs/num/.depend
index cac4b48d6..edc2107e2 100644
--- a/otherlibs/num/.depend
+++ b/otherlibs/num/.depend
@@ -1,10 +1,10 @@
nat_stubs.o: nat_stubs.c ../../byterun/alloc.h ../../byterun/misc.h \
- ../../byterun/config.h ../../byterun/../config/m.h \
- ../../byterun/../config/s.h ../../byterun/mlvalues.h \
- ../../byterun/custom.h ../../byterun/intext.h ../../byterun/io.h \
- ../../byterun/fix_code.h ../../byterun/fail.h ../../byterun/memory.h \
- ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
- ../../byterun/minor_gc.h nat.h bignum/h/BigNum.h bignum/h/BntoBnn.h
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/mlvalues.h ../../byterun/custom.h ../../byterun/intext.h \
+ ../../byterun/io.h ../../byterun/fix_code.h ../../byterun/fail.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h nat.h \
+ bignum/h/BigNum.h bignum/h/BntoBnn.h
big_int.cmi: nat.cmi
num.cmi: big_int.cmi nat.cmi ratio.cmi
ratio.cmi: big_int.cmi nat.cmi
diff --git a/otherlibs/str/.depend b/otherlibs/str/.depend
index 13deac1a6..4d370653d 100644
--- a/otherlibs/str/.depend
+++ b/otherlibs/str/.depend
@@ -1,3 +1,8 @@
-strstubs.o: strstubs.c
+strstubs.o: strstubs.c regex-0.12/regex.h ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/alloc.h ../../byterun/custom.h \
+ ../../byterun/fail.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h
str.cmo: str.cmi
str.cmx: str.cmi
diff --git a/otherlibs/threads/.depend b/otherlibs/threads/.depend
index 9b49fbb8d..d73c31e4c 100644
--- a/otherlibs/threads/.depend
+++ b/otherlibs/threads/.depend
@@ -1,12 +1,11 @@
scheduler.o: scheduler.c ../../byterun/alloc.h ../../byterun/misc.h \
- ../../byterun/config.h ../../byterun/../config/m.h \
- ../../byterun/../config/s.h ../../byterun/mlvalues.h \
- ../../byterun/backtrace.h ../../byterun/callback.h \
- ../../byterun/fail.h ../../byterun/io.h ../../byterun/memory.h \
- ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
- ../../byterun/minor_gc.h ../../byterun/printexc.h \
- ../../byterun/roots.h ../../byterun/signals.h ../../byterun/stacks.h \
- ../../byterun/sys.h
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/mlvalues.h ../../byterun/backtrace.h \
+ ../../byterun/callback.h ../../byterun/fail.h ../../byterun/io.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h \
+ ../../byterun/printexc.h ../../byterun/roots.h ../../byterun/signals.h \
+ ../../byterun/stacks.h ../../byterun/sys.h
condition.cmi: mutex.cmi
thread.cmi: unix.cmi
threadUnix.cmi: unix.cmi
@@ -14,8 +13,8 @@ condition.cmo: mutex.cmi thread.cmi condition.cmi
condition.cmx: mutex.cmx thread.cmx condition.cmi
event.cmo: condition.cmi mutex.cmi event.cmi
event.cmx: condition.cmx mutex.cmx event.cmi
-marshal.cmo: marshal.cmi
-marshal.cmx: marshal.cmi
+marshal.cmo: pervasives.cmi marshal.cmi
+marshal.cmx: pervasives.cmx marshal.cmi
mutex.cmo: thread.cmi mutex.cmi
mutex.cmx: thread.cmx mutex.cmi
pervasives.cmo: unix.cmi pervasives.cmi
diff --git a/otherlibs/unix/.depend b/otherlibs/unix/.depend
index 8759ef8b5..bb0606d18 100644
--- a/otherlibs/unix/.depend
+++ b/otherlibs/unix/.depend
@@ -1,93 +1,279 @@
-accept.o: accept.c unixsupport.h socketaddr.h
-access.o: access.c unixsupport.h
-addrofstr.o: addrofstr.c unixsupport.h socketaddr.h
-alarm.o: alarm.c unixsupport.h
-bind.o: bind.c unixsupport.h socketaddr.h
-chdir.o: chdir.c unixsupport.h
-chmod.o: chmod.c unixsupport.h
-chown.o: chown.c unixsupport.h
-chroot.o: chroot.c unixsupport.h
-close.o: close.c unixsupport.h
-closedir.o: closedir.c unixsupport.h
-connect.o: connect.c unixsupport.h socketaddr.h
-cst2constr.o: cst2constr.c cst2constr.h
-cstringv.o: cstringv.c unixsupport.h
-dup.o: dup.c unixsupport.h
-dup2.o: dup2.c unixsupport.h
-envir.o: envir.c
-errmsg.o: errmsg.c
-execv.o: execv.c unixsupport.h
-execve.o: execve.c unixsupport.h
-execvp.o: execvp.c unixsupport.h
-exit.o: exit.c unixsupport.h
-fchmod.o: fchmod.c unixsupport.h
-fchown.o: fchown.c unixsupport.h
-fcntl.o: fcntl.c unixsupport.h
-fork.o: fork.c unixsupport.h
-ftruncate.o: ftruncate.c unixsupport.h
-getcwd.o: getcwd.c unixsupport.h
-getegid.o: getegid.c unixsupport.h
-geteuid.o: geteuid.c unixsupport.h
-getgid.o: getgid.c unixsupport.h
-getgr.o: getgr.c unixsupport.h
-getgroups.o: getgroups.c unixsupport.h
-gethost.o: gethost.c unixsupport.h socketaddr.h
-gethostname.o: gethostname.c unixsupport.h
-getlogin.o: getlogin.c unixsupport.h
-getpeername.o: getpeername.c unixsupport.h socketaddr.h
-getpid.o: getpid.c unixsupport.h
-getppid.o: getppid.c unixsupport.h
-getproto.o: getproto.c unixsupport.h
-getpw.o: getpw.c unixsupport.h
-getserv.o: getserv.c unixsupport.h
-getsockname.o: getsockname.c unixsupport.h socketaddr.h
-gettimeofday.o: gettimeofday.c unixsupport.h
-getuid.o: getuid.c unixsupport.h
-gmtime.o: gmtime.c unixsupport.h
-itimer.o: itimer.c unixsupport.h
-kill.o: kill.c unixsupport.h
-link.o: link.c unixsupport.h
-listen.o: listen.c unixsupport.h
-lockf.o: lockf.c unixsupport.h
-lseek.o: lseek.c unixsupport.h
-mkdir.o: mkdir.c unixsupport.h
-mkfifo.o: mkfifo.c unixsupport.h
-nice.o: nice.c unixsupport.h
-open.o: open.c unixsupport.h
-opendir.o: opendir.c unixsupport.h
-pipe.o: pipe.c unixsupport.h
-putenv.o: putenv.c unixsupport.h
-read.o: read.c unixsupport.h
-readdir.o: readdir.c unixsupport.h
-readlink.o: readlink.c unixsupport.h
-rename.o: rename.c unixsupport.h
-rewinddir.o: rewinddir.c unixsupport.h
-rmdir.o: rmdir.c unixsupport.h
-select.o: select.c unixsupport.h
-sendrecv.o: sendrecv.c unixsupport.h socketaddr.h
-setgid.o: setgid.c unixsupport.h
-setsid.o: setsid.c unixsupport.h
-setuid.o: setuid.c unixsupport.h
-shutdown.o: shutdown.c unixsupport.h
-signals.o: signals.c unixsupport.h
-sleep.o: sleep.c unixsupport.h
-socket.o: socket.c unixsupport.h
-socketaddr.o: socketaddr.c unixsupport.h socketaddr.h
-socketpair.o: socketpair.c unixsupport.h
-sockopt.o: sockopt.c unixsupport.h socketaddr.h
-stat.o: stat.c unixsupport.h cst2constr.h
-strofaddr.o: strofaddr.c unixsupport.h socketaddr.h
-symlink.o: symlink.c unixsupport.h
-termios.o: termios.c unixsupport.h
-time.o: time.c unixsupport.h
-times.o: times.c unixsupport.h
-truncate.o: truncate.c unixsupport.h
-umask.o: umask.c unixsupport.h
-unixsupport.o: unixsupport.c unixsupport.h cst2constr.h
-unlink.o: unlink.c unixsupport.h
-utimes.o: utimes.c unixsupport.h
-wait.o: wait.c unixsupport.h
-write.o: write.c unixsupport.h
+accept.o: accept.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/signals.h unixsupport.h \
+ socketaddr.h
+access.o: access.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+addrofstr.o: addrofstr.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/fail.h unixsupport.h socketaddr.h
+alarm.o: alarm.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+bind.o: bind.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h \
+ socketaddr.h
+chdir.o: chdir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+chmod.o: chmod.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+chown.o: chown.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+chroot.o: chroot.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+close.o: close.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+closedir.o: closedir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+connect.o: connect.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/signals.h unixsupport.h socketaddr.h
+cst2constr.o: cst2constr.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/fail.h cst2constr.h
+cstringv.o: cstringv.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h unixsupport.h
+dup.o: dup.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+dup2.o: dup2.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+envir.o: envir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h
+errmsg.o: errmsg.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h
+execv.o: execv.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h unixsupport.h
+execve.o: execve.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h unixsupport.h
+execvp.o: execvp.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h unixsupport.h
+exit.o: exit.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+fchmod.o: fchmod.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+fchown.o: fchown.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+fcntl.o: fcntl.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+fork.o: fork.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+ftruncate.o: ftruncate.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/io.h unixsupport.h
+getcwd.o: getcwd.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+getegid.o: getegid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+geteuid.o: geteuid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+getgid.o: getgid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+getgr.o: getgr.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/fail.h ../../byterun/alloc.h ../../byterun/memory.h \
+ ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h unixsupport.h
+getgroups.o: getgroups.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+gethost.o: gethost.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/fail.h ../../byterun/signals.h \
+ unixsupport.h socketaddr.h
+gethostname.o: gethostname.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/alloc.h unixsupport.h
+getlogin.o: getlogin.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+getpeername.o: getpeername.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h unixsupport.h socketaddr.h
+getpid.o: getpid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+getppid.o: getppid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+getproto.o: getproto.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/fail.h unixsupport.h
+getpw.o: getpw.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/fail.h unixsupport.h
+getserv.o: getserv.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/fail.h unixsupport.h
+getsockname.o: getsockname.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h unixsupport.h socketaddr.h
+gettimeofday.o: gettimeofday.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/alloc.h unixsupport.h
+getuid.o: getuid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+gmtime.o: gmtime.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h unixsupport.h
+itimer.o: itimer.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h unixsupport.h
+kill.o: kill.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/fail.h unixsupport.h ../../byterun/signals.h
+link.o: link.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+listen.o: listen.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+lockf.o: lockf.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+lseek.o: lseek.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/io.h unixsupport.h
+mkdir.o: mkdir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+mkfifo.o: mkfifo.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+nice.o: nice.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+open.o: open.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+opendir.o: opendir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+pipe.o: pipe.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+putenv.o: putenv.c ../../byterun/memory.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/gc.h \
+ ../../byterun/mlvalues.h ../../byterun/misc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h unixsupport.h
+read.o: read.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h \
+ ../../byterun/signals.h unixsupport.h
+readdir.o: readdir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/fail.h ../../byterun/alloc.h unixsupport.h
+readlink.o: readlink.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+rename.o: rename.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+rewinddir.o: rewinddir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+rmdir.o: rmdir.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+select.o: select.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/signals.h unixsupport.h
+sendrecv.o: sendrecv.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/signals.h unixsupport.h \
+ socketaddr.h
+setgid.o: setgid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+setsid.o: setsid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+setuid.o: setuid.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+shutdown.o: shutdown.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+signals.o: signals.c ../../byterun/alloc.h ../../byterun/misc.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/mlvalues.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/signals.h unixsupport.h
+sleep.o: sleep.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/signals.h unixsupport.h
+socket.o: socket.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+socketaddr.o: socketaddr.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/alloc.h ../../byterun/memory.h \
+ ../../byterun/gc.h ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h unixsupport.h socketaddr.h
+socketpair.o: socketpair.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/alloc.h unixsupport.h
+sockopt.o: sockopt.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h socketaddr.h
+stat.o: stat.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h ../../byterun/alloc.h \
+ unixsupport.h cst2constr.h ../../byterun/io.h
+strofaddr.o: strofaddr.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h socketaddr.h
+symlink.o: symlink.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+termios.o: termios.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+time.o: time.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h unixsupport.h
+times.o: times.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h unixsupport.h
+truncate.o: truncate.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/io.h unixsupport.h
+umask.o: umask.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+unixsupport.o: unixsupport.c ../../byterun/mlvalues.h \
+ ../../byterun/config.h ../../config/m.h ../../config/s.h \
+ ../../byterun/misc.h ../../byterun/alloc.h ../../byterun/callback.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h ../../byterun/fail.h \
+ unixsupport.h cst2constr.h
+unlink.o: unlink.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+utimes.o: utimes.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h unixsupport.h
+wait.o: wait.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/alloc.h ../../byterun/memory.h ../../byterun/gc.h \
+ ../../byterun/major_gc.h ../../byterun/freelist.h \
+ ../../byterun/minor_gc.h ../../byterun/signals.h unixsupport.h
+write.o: write.c ../../byterun/mlvalues.h ../../byterun/config.h \
+ ../../config/m.h ../../config/s.h ../../byterun/misc.h \
+ ../../byterun/memory.h ../../byterun/gc.h ../../byterun/major_gc.h \
+ ../../byterun/freelist.h ../../byterun/minor_gc.h \
+ ../../byterun/signals.h unixsupport.h
unixLabels.cmi: unix.cmi
unix.cmo: unix.cmi
unix.cmx: unix.cmi