deuxieme tranche des travaux de depollution (PR#1914 et PR#1956) + dependances

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6020 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2003-12-15 16:29:53 +00:00
parent fd7e2a7cb9
commit 8fde08275d
20 changed files with 169 additions and 125 deletions

View File

@ -13,10 +13,11 @@
/* $Id$ */
#ifndef _custom_
#define _custom_
#ifndef CAML_CUSTOM_H
#define CAML_CUSTOM_H
#include "compatibility.h"
#include "mlvalues.h"
struct custom_operations {
@ -52,4 +53,4 @@ extern struct custom_operations * final_custom_operations(void (*fn)(value));
extern void init_custom_operations(void);
/* </private> */
#endif
#endif /* CAML_CUSTOM_H */

View File

@ -13,12 +13,14 @@
/* $Id$ */
#ifndef _fail_
#define _fail_
#ifndef CAML_FAIL_H
#define CAML_FAIL_H
/* <private> */
#include <setjmp.h>
/* </private> */
#include "compatibility.h"
#include "misc.h"
#include "mlvalues.h"
@ -69,4 +71,4 @@ CAMLextern void init_exceptions (void);
CAMLextern void array_bound_error (void) Noreturn;
CAMLextern void raise_sys_blocked_io (void) Noreturn;
#endif /* _fail_ */
#endif /* CAML_FAIL_H */

View File

@ -15,9 +15,10 @@
/* Structured input/output */
#ifndef __intext__
#define __intext__
#ifndef CAML_INTEXT_H
#define CAML_INTEXT_H
#include "compatibility.h"
#include "misc.h"
#include "mlvalues.h"
@ -170,5 +171,4 @@ extern char * code_area_start, * code_area_end;
/* </private> */
#endif
#endif /* CAML_INTEXT_H */

View File

@ -114,7 +114,7 @@ CAMLexport file_offset channel_size(struct channel *channel)
end = lseek(channel->fd, 0, SEEK_END);
if (end == -1 ||
lseek(channel->fd, channel->offset, SEEK_SET) != channel->offset) {
sys_error(NO_ARG);
caml_sys_error(NO_ARG);
}
return end;
}
@ -166,7 +166,7 @@ again:
}
}
#endif
if (retcode == -1) sys_error(NO_ARG);
if (retcode == -1) caml_sys_error(NO_ARG);
return retcode;
}
@ -247,7 +247,7 @@ CAMLexport void really_putblock(struct channel *channel, char *p, long int len)
CAMLexport void seek_out(struct channel *channel, file_offset dest)
{
flush(channel);
if (lseek(channel->fd, dest, SEEK_SET) != dest) sys_error(NO_ARG);
if (lseek(channel->fd, dest, SEEK_SET) != dest) caml_sys_error(NO_ARG);
channel->offset = dest;
}
@ -275,7 +275,7 @@ CAMLexport int do_read(int fd, char *p, unsigned int n)
#endif
#endif
leave_blocking_section();
if (retcode == -1) sys_error(NO_ARG);
if (retcode == -1) caml_sys_error(NO_ARG);
return retcode;
}
@ -348,7 +348,7 @@ CAMLexport void seek_in(struct channel *channel, file_offset dest)
dest <= channel->offset) {
channel->curr = channel->max - (channel->offset - dest);
} else {
if (lseek(channel->fd, dest, SEEK_SET) != dest) sys_error(NO_ARG);
if (lseek(channel->fd, dest, SEEK_SET) != dest) caml_sys_error(NO_ARG);
channel->offset = dest;
channel->curr = channel->max = channel->buff;
}
@ -474,7 +474,7 @@ CAMLprim value caml_out_channels_list (value unit)
CAMLprim value channel_descriptor(value vchannel)
{
int fd = Channel(vchannel)->fd;
if (fd == -1) { errno = EBADF; sys_error(NO_ARG); }
if (fd == -1) { errno = EBADF; caml_sys_error(NO_ARG); }
return Val_int(fd);
}
@ -494,7 +494,7 @@ CAMLprim value caml_close_channel(value vchannel)
immediate flush_partial or refill, thus raising a Sys_error
exception */
channel->curr = channel->max = channel->end;
if (result == -1) sys_error (NO_ARG);
if (result == -1) caml_sys_error (NO_ARG);
return Val_unit;
}
@ -510,7 +510,7 @@ CAMLprim value caml_close_channel(value vchannel)
CAMLprim value caml_channel_size(value vchannel)
{
file_offset size = channel_size(Channel(vchannel));
if (size > Max_long) { errno = EOVERFLOW; sys_error(NO_ARG); }
if (size > Max_long) { errno = EOVERFLOW; caml_sys_error(NO_ARG); }
return Val_long(size);
}
@ -524,7 +524,7 @@ CAMLprim value caml_set_binary_mode(value vchannel, value mode)
#ifdef _WIN32
struct channel * channel = Channel(vchannel);
if (setmode(channel->fd, Bool_val(mode) ? O_BINARY : O_TEXT) == -1)
sys_error(NO_ARG);
caml_sys_error(NO_ARG);
#endif
return Val_unit;
}
@ -627,7 +627,7 @@ CAMLprim value caml_seek_out_64(value vchannel, value pos)
CAMLprim value caml_pos_out(value vchannel)
{
file_offset pos = pos_out(Channel(vchannel));
if (pos > Max_long) { errno = EOVERFLOW; sys_error(NO_ARG); }
if (pos > Max_long) { errno = EOVERFLOW; caml_sys_error(NO_ARG); }
return Val_long(pos);
}
@ -714,7 +714,7 @@ CAMLprim value caml_seek_in_64(value vchannel, value pos)
CAMLprim value caml_pos_in(value vchannel)
{
file_offset pos = pos_in(Channel(vchannel));
if (pos > Max_long) { errno = EOVERFLOW; sys_error(NO_ARG); }
if (pos > Max_long) { errno = EOVERFLOW; caml_sys_error(NO_ARG); }
return Val_long(pos);
}

View File

@ -15,10 +15,11 @@
/* Allocation macros and functions */
#ifndef _memory_
#define _memory_
#ifndef CAML_MEMORY_H
#define CAML_MEMORY_H
#include "compatibility.h"
#include "config.h"
/* <private> */
#include "gc.h"
@ -373,5 +374,4 @@ CAMLextern void register_global_root (value *);
CAMLextern void remove_global_root (value *);
#endif /* _memory_ */
#endif /* CAML_MEMORY_H */

View File

@ -15,10 +15,11 @@
/* Miscellaneous macros and variables. */
#ifndef _misc_
#define _misc_
#ifndef CAML_MISC_H
#define CAML_MISC_H
#include "compatibility.h"
#include "config.h"
/* Standard definitions */
@ -139,4 +140,4 @@ char *aligned_malloc (asize_t, int, void **);
/* </private> */
#endif /* _misc_ */
#endif /* CAML_MISC_H */

View File

@ -17,6 +17,7 @@
#define CAML_MLVALUES_H
#include "compatibility.h"
#include "config.h"
#include "misc.h"

View File

@ -270,11 +270,11 @@ CAMLprim value install_signal_handler(value signal_number, value action)
sigact.sa_handler = act;
sigemptyset(&sigact.sa_mask);
sigact.sa_flags = 0;
if (sigaction(sig, &sigact, &oldsigact) == -1) sys_error(NO_ARG);
if (sigaction(sig, &sigact, &oldsigact) == -1) caml_sys_error(NO_ARG);
oldact = oldsigact.sa_handler;
#else
oldact = signal(sig, act);
if (oldact == SIG_ERR) sys_error(NO_ARG);
if (oldact == SIG_ERR) caml_sys_error(NO_ARG);
#endif
if (oldact == handle_signal) {
res = alloc_small (1, 0); /* Signal_handle */

View File

@ -13,9 +13,10 @@
/* $Id$ */
#ifndef _signals_
#define _signals_
#ifndef CAML_SIGNALS_H
#define CAML_SIGNALS_H
#include "compatibility.h"
#include "misc.h"
#include "mlvalues.h"
@ -41,5 +42,4 @@ CAMLextern void (*leave_blocking_section_hook)(void);
CAMLextern void (* volatile async_action_hook)(void);
/* </private> */
#endif /* _signals_ */
#endif /* CAML_SIGNALS_H */

View File

@ -65,7 +65,7 @@ extern int errno;
extern char * strerror(int);
#endif
char * error_message(void)
static char * error_message(void)
{
return strerror(errno);
}
@ -75,7 +75,7 @@ char * error_message(void)
extern int sys_nerr;
extern char * sys_errlist [];
char * error_message(void)
static char * error_message(void)
{
if (errno < 0 || errno >= sys_nerr)
return "unknown error";
@ -92,7 +92,7 @@ char * error_message(void)
#define EWOULDBLOCK (-1)
#endif
CAMLexport void sys_error(value arg)
CAMLexport void caml_sys_error(value arg)
{
CAMLparam1 (arg);
char * err;
@ -165,7 +165,7 @@ CAMLprim value caml_sys_open(value path, value flags, value perm)
);
leave_blocking_section();
stat_free(p);
if (fd == -1) sys_error(path);
if (fd == -1) caml_sys_error(path);
#if defined(F_SETFD) && defined(FD_CLOEXEC)
fcntl(fd, F_SETFD, FD_CLOEXEC);
#endif
@ -196,20 +196,20 @@ CAMLprim value sys_remove(value name)
{
int ret;
ret = unlink(String_val(name));
if (ret != 0) sys_error(name);
if (ret != 0) caml_sys_error(name);
return Val_unit;
}
CAMLprim value sys_rename(value oldname, value newname)
{
if (rename(String_val(oldname), String_val(newname)) != 0)
sys_error(oldname);
caml_sys_error(oldname);
return Val_unit;
}
CAMLprim value sys_chdir(value dirname)
{
if (chdir(String_val(dirname)) != 0) sys_error(dirname);
if (chdir(String_val(dirname)) != 0) caml_sys_error(dirname);
return Val_unit;
}
@ -217,9 +217,9 @@ CAMLprim value sys_getcwd(value unit)
{
char buff[4096];
#ifdef HAS_GETCWD
if (getcwd(buff, sizeof(buff)) == 0) sys_error(NO_ARG);
if (getcwd(buff, sizeof(buff)) == 0) caml_sys_error(NO_ARG);
#else
if (getwd(buff) == 0) sys_error(NO_ARG);
if (getwd(buff) == 0) caml_sys_error(NO_ARG);
#endif /* HAS_GETCWD */
return copy_string(buff);
}
@ -279,7 +279,7 @@ CAMLprim value sys_system_command(value command)
status = system(buf);
leave_blocking_section ();
stat_free(buf);
if (status == -1) sys_error(command);
if (status == -1) caml_sys_error(command);
if (WIFEXITED(status))
retcode = WEXITSTATUS(status);
else
@ -341,7 +341,7 @@ CAMLprim value sys_read_directory(value path)
struct ext_table tbl;
ext_table_init(&tbl, 50);
if (caml_read_directory(String_val(path), &tbl) == -1) sys_error(path);
if (caml_read_directory(String_val(path), &tbl) == -1) caml_sys_error(path);
ext_table_add(&tbl, NULL);
result = copy_string_array((char const **) tbl.contents);
ext_table_free(&tbl, 1);

View File

@ -20,7 +20,7 @@
#define NO_ARG Val_int(0)
CAMLextern void sys_error (value);
CAMLextern void caml_sys_error (value);
extern void sys_init (char * exe_name, char ** argv);
CAMLextern value sys_exit (value);

View File

@ -11,6 +11,8 @@ ast2pt.cmo: $(OTOP)/parsing/asttypes.cmi $(OTOP)/parsing/location.cmi \
ast2pt.cmx: $(OTOP)/parsing/asttypes.cmi $(OTOP)/parsing/location.cmx \
$(OTOP)/parsing/longident.cmx mLast.cmi $(OTOP)/parsing/parsetree.cmi \
ast2pt.cmi
crc.cmo: $(OTOP)/otherlibs/dynlink/dynlink.cmi
crc.cmx: $(OTOP)/otherlibs/dynlink/dynlink.cmx
pcaml.cmo: ast2pt.cmi mLast.cmi quotation.cmi reloc.cmi spretty.cmi pcaml.cmi
pcaml.cmx: ast2pt.cmx mLast.cmi quotation.cmx reloc.cmx spretty.cmx pcaml.cmi
quotation.cmo: mLast.cmi quotation.cmi

View File

@ -1,4 +1,6 @@
compile.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
compile.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
comp_trail.cmo: ../camlp4/pcaml.cmi
comp_trail.cmx: ../camlp4/pcaml.cmx
compile.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
compile.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_o_fast.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_o_fast.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx

View File

@ -15,6 +15,8 @@ pa_lisp.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_lisp.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_lispr.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_lispr.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_o.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_o.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_ocamllex.cmo: $(OTOP)/lex/compact.cmi $(OTOP)/lex/cset.cmi \
$(OTOP)/lex/lexgen.cmi ../camlp4/mLast.cmi ../camlp4/pcaml.cmi \
$(OTOP)/lex/syntax.cmi
@ -23,14 +25,10 @@ pa_ocamllex.cmx: $(OTOP)/lex/compact.cmx $(OTOP)/lex/cset.cmx \
$(OTOP)/lex/syntax.cmx
pa_olabl.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_olabl.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_o.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_o.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_oop.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_oop.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_op.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_op.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
parserify.cmo: ../camlp4/mLast.cmi parserify.cmi
parserify.cmx: ../camlp4/mLast.cmi parserify.cmi
pa_ru.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_ru.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_scheme.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
@ -39,6 +37,8 @@ pa_schemer.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_schemer.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pa_sml.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pa_sml.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
parserify.cmo: ../camlp4/mLast.cmi parserify.cmi
parserify.cmx: ../camlp4/mLast.cmi parserify.cmi
pr_depend.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pr_depend.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pr_extend.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
@ -49,20 +49,20 @@ pr_null.cmo: ../camlp4/pcaml.cmi
pr_null.cmx: ../camlp4/pcaml.cmx
pr_o.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
pr_o.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx ../camlp4/spretty.cmx
pr_op.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
pr_op.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx ../camlp4/spretty.cmx
pr_op_main.cmo: ../camlp4/mLast.cmi parserify.cmi ../camlp4/pcaml.cmi \
../camlp4/spretty.cmi
pr_op_main.cmx: ../camlp4/mLast.cmi parserify.cmx ../camlp4/pcaml.cmx \
../camlp4/spretty.cmx
pr_op.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
pr_op.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx ../camlp4/spretty.cmx
pr_r.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
pr_r.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx ../camlp4/spretty.cmx
pr_rp.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
pr_rp.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx ../camlp4/spretty.cmx
pr_rp_main.cmo: ../camlp4/mLast.cmi parserify.cmi ../camlp4/pcaml.cmi \
../camlp4/spretty.cmi
pr_rp_main.cmx: ../camlp4/mLast.cmi parserify.cmx ../camlp4/pcaml.cmx \
../camlp4/spretty.cmx
pr_rp.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi ../camlp4/spretty.cmi
pr_rp.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx ../camlp4/spretty.cmx
pr_scheme.cmo: ../camlp4/mLast.cmi ../camlp4/pcaml.cmi
pr_scheme.cmx: ../camlp4/mLast.cmi ../camlp4/pcaml.cmx
pr_schp_main.cmo: ../camlp4/mLast.cmi parserify.cmi ../camlp4/pcaml.cmi \

View File

@ -1,6 +1,6 @@
odyl.cmo: odyl_config.cmo odyl_main.cmi
odyl.cmx: odyl_config.cmx odyl_main.cmx
odyl_main.cmo: $(OTOP)/otherlibs/dynlink/dynlink.cmi odyl_config.cmo \
odyl_main.cmi
odyl_main.cmx: odyl_config.cmx \
odyl_main.cmi
odyl.cmo: odyl_config.cmo odyl_main.cmi
odyl.cmx: odyl_config.cmx odyl_main.cmx

View File

@ -104,15 +104,15 @@ loadprinter.cmx: ../utils/config.cmx ../typing/ctype.cmx debugger_config.cmx \
../typing/printtyp.cmx printval.cmx ../bytecomp/symtable.cmx \
../typing/types.cmx loadprinter.cmi
main.cmo: checkpoints.cmi command_line.cmi ../utils/config.cmi \
debugger_config.cmi exec.cmi frames.cmi input_handling.cmi \
../utils/misc.cmi parameters.cmi primitives.cmi program_management.cmi \
show_information.cmi time_travel.cmi ../otherlibs/unix/unix.cmi \
unix_tools.cmi
debugger_config.cmi ../typing/env.cmi exec.cmi frames.cmi \
input_handling.cmi ../utils/misc.cmi parameters.cmi primitives.cmi \
program_management.cmi show_information.cmi time_travel.cmi \
../otherlibs/unix/unix.cmi unix_tools.cmi
main.cmx: checkpoints.cmx command_line.cmx ../utils/config.cmx \
debugger_config.cmx exec.cmx frames.cmx input_handling.cmx \
../utils/misc.cmx parameters.cmx primitives.cmx program_management.cmx \
show_information.cmx time_travel.cmx ../otherlibs/unix/unix.cmx \
unix_tools.cmx
debugger_config.cmx ../typing/env.cmx exec.cmx frames.cmx \
input_handling.cmx ../utils/misc.cmx parameters.cmx primitives.cmx \
program_management.cmx show_information.cmx time_travel.cmx \
../otherlibs/unix/unix.cmx unix_tools.cmx
parameters.cmo: ../utils/config.cmi envaux.cmi ../utils/misc.cmi \
primitives.cmi parameters.cmi
parameters.cmx: ../utils/config.cmx envaux.cmx ../utils/misc.cmx \

View File

@ -90,15 +90,17 @@ odoc_html.cmo: odoc_dag2html.cmi odoc_info.cmi odoc_messages.cmo \
odoc_ocamlhtml.cmo odoc_text.cmi
odoc_html.cmx: odoc_dag2html.cmx odoc_info.cmx odoc_messages.cmx \
odoc_ocamlhtml.cmx odoc_text.cmx
odoc_info.cmo: odoc_analyse.cmi odoc_args.cmi odoc_class.cmo odoc_dep.cmo \
odoc_exception.cmo odoc_global.cmi odoc_messages.cmo odoc_misc.cmi \
odoc_module.cmo odoc_name.cmi odoc_parameter.cmo odoc_scan.cmo \
odoc_search.cmi odoc_str.cmi odoc_type.cmo odoc_types.cmi odoc_value.cmo \
odoc_info.cmo: odoc_analyse.cmi odoc_args.cmi odoc_class.cmo \
odoc_comments.cmi odoc_dep.cmo odoc_exception.cmo odoc_global.cmi \
odoc_messages.cmo odoc_misc.cmi odoc_module.cmo odoc_name.cmi \
odoc_parameter.cmo odoc_scan.cmo odoc_search.cmi odoc_str.cmi \
odoc_text.cmi odoc_type.cmo odoc_types.cmi odoc_value.cmo \
../typing/printtyp.cmi odoc_info.cmi
odoc_info.cmx: odoc_analyse.cmx odoc_args.cmx odoc_class.cmx odoc_dep.cmx \
odoc_exception.cmx odoc_global.cmx odoc_messages.cmx odoc_misc.cmx \
odoc_module.cmx odoc_name.cmx odoc_parameter.cmx odoc_scan.cmx \
odoc_search.cmx odoc_str.cmx odoc_type.cmx odoc_types.cmx odoc_value.cmx \
odoc_info.cmx: odoc_analyse.cmx odoc_args.cmx odoc_class.cmx \
odoc_comments.cmx odoc_dep.cmx odoc_exception.cmx odoc_global.cmx \
odoc_messages.cmx odoc_misc.cmx odoc_module.cmx odoc_name.cmx \
odoc_parameter.cmx odoc_scan.cmx odoc_search.cmx odoc_str.cmx \
odoc_text.cmx odoc_type.cmx odoc_types.cmx odoc_value.cmx \
../typing/printtyp.cmx odoc_info.cmi
odoc_latex.cmo: odoc_info.cmi odoc_latex_style.cmo odoc_messages.cmo \
odoc_to_text.cmo
@ -108,8 +110,8 @@ odoc_lexer.cmo: odoc_args.cmi odoc_comments_global.cmi odoc_messages.cmo \
odoc_parser.cmi
odoc_lexer.cmx: odoc_args.cmx odoc_comments_global.cmx odoc_messages.cmx \
odoc_parser.cmx
odoc_man.cmo: odoc_info.cmi odoc_messages.cmo odoc_misc.cmi
odoc_man.cmx: odoc_info.cmx odoc_messages.cmx odoc_misc.cmx
odoc_man.cmo: odoc_info.cmi odoc_messages.cmo odoc_misc.cmi odoc_str.cmi
odoc_man.cmx: odoc_info.cmx odoc_messages.cmx odoc_misc.cmx odoc_str.cmx
odoc_merge.cmo: odoc_args.cmi odoc_class.cmo odoc_exception.cmo \
odoc_messages.cmo odoc_module.cmo odoc_name.cmi odoc_parameter.cmo \
odoc_type.cmo odoc_types.cmi odoc_value.cmo odoc_merge.cmi
@ -175,13 +177,17 @@ odoc_sig.cmx: ../parsing/asttypes.cmi ../typing/btype.cmx \
../parsing/parsetree.cmi ../typing/path.cmx ../typing/typedtree.cmx \
../typing/types.cmx odoc_sig.cmi
odoc_str.cmo: odoc_exception.cmo odoc_messages.cmo odoc_misc.cmi \
odoc_name.cmi odoc_type.cmo odoc_value.cmo odoc_str.cmi
odoc_name.cmi odoc_type.cmo odoc_value.cmo ../typing/printtyp.cmi \
../typing/types.cmi odoc_str.cmi
odoc_str.cmx: odoc_exception.cmx odoc_messages.cmx odoc_misc.cmx \
odoc_name.cmx odoc_type.cmx odoc_value.cmx odoc_str.cmi
odoc_name.cmx odoc_type.cmx odoc_value.cmx ../typing/printtyp.cmx \
../typing/types.cmx odoc_str.cmi
odoc_texi.cmo: odoc_info.cmi odoc_messages.cmo odoc_to_text.cmo
odoc_texi.cmx: odoc_info.cmx odoc_messages.cmx odoc_to_text.cmx
odoc_text.cmo: odoc_text_lexer.cmo odoc_text_parser.cmi odoc_text.cmi
odoc_text.cmx: odoc_text_lexer.cmx odoc_text_parser.cmx odoc_text.cmi
odoc_text.cmo: odoc_text_lexer.cmo odoc_text_parser.cmi odoc_types.cmi \
odoc_text.cmi
odoc_text.cmx: odoc_text_lexer.cmx odoc_text_parser.cmx odoc_types.cmx \
odoc_text.cmi
odoc_text_lexer.cmo: odoc_text_parser.cmi
odoc_text_lexer.cmx: odoc_text_parser.cmx
odoc_text_parser.cmo: odoc_types.cmi odoc_text_parser.cmi
@ -217,6 +223,7 @@ odoc_search.cmi: odoc_class.cmo odoc_exception.cmo odoc_module.cmo \
odoc_type.cmo odoc_types.cmi odoc_value.cmo
odoc_sig.cmi: odoc_class.cmo odoc_env.cmi odoc_module.cmo odoc_name.cmi \
odoc_type.cmo odoc_types.cmi ../parsing/parsetree.cmi ../typing/types.cmi
odoc_str.cmi: odoc_exception.cmo odoc_type.cmo odoc_value.cmo
odoc_str.cmi: odoc_exception.cmo odoc_type.cmo odoc_value.cmo \
../typing/types.cmi
odoc_text.cmi: odoc_types.cmi
odoc_text_parser.cmi: odoc_types.cmi

View File

@ -1,47 +1,74 @@
color.o: color.c libgraph.h ../../byterun/mlvalues.h \
../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h
draw.o: draw.c libgraph.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 ../../byterun/mlvalues.h \
../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h image.h ../../byterun/alloc.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 ../../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 ../../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 ../../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 ../../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 \
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
open.o: open.c libgraph.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 ../../byterun/mlvalues.h \
../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h
sound.o: sound.c libgraph.h ../../byterun/mlvalues.h \
../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h
subwindow.o: subwindow.c libgraph.h ../../byterun/mlvalues.h \
../../byterun/config.h ../../config/m.h ../../config/s.h \
../../byterun/misc.h
text.o: text.c libgraph.h ../../byterun/mlvalues.h ../../byterun/config.h \
../../config/m.h ../../config/s.h ../../byterun/misc.h \
../../byterun/alloc.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

View File

@ -1,6 +1,6 @@
bng.o: bng.c bng.h bng_ppc.c bng_digit.c
bng_alpha.o: bng_alpha.c
bng_amd64.o: bng_amd64.c
bng.o: bng.c bng.h bng_ia32.c bng_digit.c
bng_digit.o: bng_digit.c
bng_ia32.o: bng_ia32.c
bng_mips.o: bng_mips.c

View File

@ -1,3 +1,4 @@
camlinternalOO.cmi: obj.cmi
format.cmi: buffer.cmi
genlex.cmi: stream.cmi
moreLabels.cmi: hashtbl.cmi map.cmi set.cmi
@ -76,9 +77,9 @@ random.cmo: array.cmi char.cmi digest.cmi int32.cmi int64.cmi nativeint.cmi \
pervasives.cmi string.cmi random.cmi
random.cmx: array.cmx char.cmx digest.cmx int32.cmx int64.cmx nativeint.cmx \
pervasives.cmx string.cmx random.cmi
scanf.cmo: array.cmi buffer.cmi list.cmi obj.cmi printf.cmi string.cmi \
scanf.cmo: buffer.cmi hashtbl.cmi list.cmi obj.cmi printf.cmi string.cmi \
sys.cmi scanf.cmi
scanf.cmx: array.cmx buffer.cmx list.cmx obj.cmx printf.cmx string.cmx \
scanf.cmx: buffer.cmx hashtbl.cmx list.cmx obj.cmx printf.cmx string.cmx \
sys.cmx scanf.cmi
set.cmo: set.cmi
set.cmx: set.cmi