summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2000-04-24 15:15:59 +0000
committerDamien Doligez <damien.doligez-inria.fr>2000-04-24 15:15:59 +0000
commitfe26502b05f10377a0a5dafcf2ecea8c5dd469f7 (patch)
treeaf30e2805ec0e5e8af5a10354900eb322757526e
parent26f96299d2c6e3ad20a184dadc94eb8a8d3cb044 (diff)
MacOS: bugs dans graphics; suppression toplevel/68k; dependances
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3135 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--Changes4
-rw-r--r--Makefile.Mac.depend16
-rw-r--r--byterun/Makefile.Mac.depend4
-rw-r--r--maccaml/Makefile.Mac14
-rw-r--r--maccaml/Makefile.Mac.depend10
-rw-r--r--maccaml/graph.c143
-rw-r--r--otherlibs/bigarray/Makefile.Mac.depend4
-rw-r--r--otherlibs/macosunix/Makefile.Mac.depend4
-rw-r--r--otherlibs/num/Makefile.Mac.depend4
-rw-r--r--otherlibs/str/Makefile.Mac.depend4
-rw-r--r--otherlibs/systhreads/Makefile.Mac.depend4
11 files changed, 121 insertions, 90 deletions
diff --git a/Changes b/Changes
index 43a4b4847..d1d08ec97 100644
--- a/Changes
+++ b/Changes
@@ -102,6 +102,10 @@ New or updated ports:
Macintosh port:
- Implemented the Unix and Thread libraries.
+- The toplevel application does not work on 68k Macintoshes; maybe
+ later if there's a demand.
+- Added a new tool, ocamlmkappli, to build an application from a
+ program written in O'Caml.
Objective Caml 2.04:
diff --git a/Makefile.Mac.depend b/Makefile.Mac.depend
index 322a9dad7..9354c651f 100644
--- a/Makefile.Mac.depend
+++ b/Makefile.Mac.depend
@@ -6,12 +6,10 @@
:utils:clflags.cmxÄ :utils:config.cmx
:utils:config.cmoÄ :utils:config.cmi
:utils:config.cmxÄ :utils:config.cmi
-:utils:formatmsg.cmoÄ :utils:formatmsg.cmi
-:utils:formatmsg.cmxÄ :utils:formatmsg.cmi
:utils:misc.cmoÄ :utils:misc.cmi
:utils:misc.cmxÄ :utils:misc.cmi
-:utils:tbl.cmoÄ :utils:formatmsg.cmi :utils:tbl.cmi
-:utils:tbl.cmxÄ :utils:formatmsg.cmx :utils:tbl.cmi
+:utils:tbl.cmoÄ :utils:tbl.cmi
+:utils:tbl.cmxÄ :utils:tbl.cmi
:utils:terminfo.cmoÄ :utils:terminfo.cmi
:utils:terminfo.cmxÄ :utils:terminfo.cmi
:utils:warnings.cmoÄ :utils:warnings.cmi
@@ -47,12 +45,10 @@
:parsing:parser.cmxÄ :parsing:asttypes.cmi :utils:clflags.cmx ¶
:parsing:location.cmx :parsing:longident.cmx :parsing:parsetree.cmi ¶
:parsing:pstream.cmx :parsing:syntaxerr.cmx :parsing:parser.cmi
-:parsing:printast.cmoÄ :parsing:asttypes.cmi :utils:formatmsg.cmi ¶
- :parsing:location.cmi :parsing:longident.cmi :parsing:parsetree.cmi ¶
- :parsing:printast.cmi
-:parsing:printast.cmxÄ :parsing:asttypes.cmi :utils:formatmsg.cmx ¶
- :parsing:location.cmx :parsing:longident.cmx :parsing:parsetree.cmi ¶
- :parsing:printast.cmi
+:parsing:printast.cmoÄ :parsing:asttypes.cmi :parsing:location.cmi ¶
+ :parsing:longident.cmi :parsing:parsetree.cmi :parsing:printast.cmi
+:parsing:printast.cmxÄ :parsing:asttypes.cmi :parsing:location.cmx ¶
+ :parsing:longident.cmx :parsing:parsetree.cmi :parsing:printast.cmi
:parsing:pstream.cmoÄ :parsing:asttypes.cmi :parsing:location.cmi ¶
:parsing:longident.cmi :parsing:parsetree.cmi :parsing:pstream.cmi
:parsing:pstream.cmxÄ :parsing:asttypes.cmi :parsing:location.cmx ¶
diff --git a/byterun/Makefile.Mac.depend b/byterun/Makefile.Mac.depend
index 7341c3ec2..8d7ece8c0 100644
--- a/byterun/Makefile.Mac.depend
+++ b/byterun/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:23:24 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:23:03 on 24 avr 2000 by MakeDepend
:alloc.c.x Ä ¶
:alloc.c ¶
@@ -1090,7 +1090,7 @@
"{CIncludes}"DateTimeUtils.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:23:42 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:23:18 on 24 avr 2000 by MakeDepend
:alloc.c.o Ä ¶
:alloc.c ¶
diff --git a/maccaml/Makefile.Mac b/maccaml/Makefile.Mac
index fd4346d6e..c12ee7f0f 100644
--- a/maccaml/Makefile.Mac
+++ b/maccaml/Makefile.Mac
@@ -12,6 +12,10 @@
# $Id$
+#FIXME Disabled the 68k stuff because GUSI seems to hang during
+# initialisation. I don't have the time to debug this. Let's see if
+# there's anyone left who wants O'Caml on 68k Macs.
+
VERSIONSTR = ¶
"¶"{OCAMLMAJOR}.{OCAMLMINOR}/Mac{MAJOR}.{MINOR}.{BUGFIX}{STAGE}{REV}¶""
@@ -31,8 +35,9 @@ CamlrunLibs = ::otherlibs:num:libnums.o ¶
::otherlibs:macosunix:libcamlrun-unix.o
WELibs = ":WASTE:WASTE 1.3 Distribution:WASTELib.o"
gusilibs = "{gusi}lib:gusi_mpw.sc.lib" ¶
- "{gusi}lib:gusi_stdio.sc.lib" ¶
- "{gusi}lib:gusi_core.sc.lib"
+ "{gusi}lib:gusi_sfio.sc.lib" ¶
+ "{gusi}lib:gusi_core.sc.lib" ¶
+ "{sfio}lib:sfio.sc.lib"
SysLibs = "{libraries}sio.far.o" ¶
"{CLibraries}CPlusLib.o" ¶
"{CLibraries}StdCLib.far.o" ¶
@@ -140,8 +145,9 @@ OCaml.68k Ä {OBJS} {camlrunlibs}
dummy_fragment Ä dummy_fragment.c.x
ppclink -xm l -o dummy_fragment {ppclinkoptions} dummy_fragment.c.x
-appli ÄÄ OCaml.PPC OCaml.68k dummy_fragment
- duplicate -y OCaml.68k appli
+appli ÄÄ OCaml.PPC dummy_fragment #FIXME OCaml.68k
+ #FIXME duplicate -y OCaml.68k appli
+ delete -i appli #FIXME
mergefragment -a OCaml.PPC appli
mergefragment dummy_fragment appli
diff --git a/maccaml/Makefile.Mac.depend b/maccaml/Makefile.Mac.depend
index 0c9243017..8b1b1665c 100644
--- a/maccaml/Makefile.Mac.depend
+++ b/maccaml/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 15:17:32 on 20 avr 2000 by MakeDepend
+# These dependencies were produced at 14:25:14 on 24 avr 2000 by MakeDepend
:aboutbox.c.x Ä ¶
:aboutbox.c ¶
@@ -1351,6 +1351,9 @@
"{CIncludes}"MachineExceptions.h ¶
"{CIncludes}"DriverSynchronization.h
+:nothreads.c.x Ä ¶
+ :nothreads.c
+
:prefs.c.x Ä ¶
:prefs.c ¶
:main.h ¶
@@ -1691,7 +1694,7 @@
"{CIncludes}"DriverSynchronization.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 15:17:41 on 20 avr 2000 by MakeDepend
+# These dependencies were produced at 14:25:23 on 24 avr 2000 by MakeDepend
:aboutbox.c.o Ä ¶
:aboutbox.c ¶
@@ -3043,6 +3046,9 @@
"{CIncludes}"MachineExceptions.h ¶
"{CIncludes}"DriverSynchronization.h
+:nothreads.c.o Ä ¶
+ :nothreads.c
+
:prefs.c.o Ä ¶
:prefs.c ¶
:main.h ¶
diff --git a/maccaml/graph.c b/maccaml/graph.c
index d6c1700fe..59cf46cf7 100644
--- a/maccaml/graph.c
+++ b/maccaml/graph.c
@@ -40,15 +40,15 @@ RGBColor fgcolor;
/* Convert from Caml coordinates to QD coordinates in the off-screen buffer. */
/* Note: these conversions are self-inverse (see gr_current_point). */
#define Bx(x) (x)
-#define By(y) (h0 - (y))
+#define By(y) (h0-1 - (y))
/* Convert from Caml coordinates to QD coordinates in the window. */
-#define Wx(x) ((x) + x0)
-#define Wy(y) ((h0 - (y)) + y0)
+#define Wx(x) (Bx(x) + x0)
+#define Wy(y) (By(y) + y0)
/* Convert from QD window coordinates to Caml coordinates. */
#define Cx(x) ((x) - x0)
-#define Cy(y) (h0 - ((y) - y0))
+#define Cy(y) (h0-1 - ((y) - y0))
/***********************************************************************/
@@ -237,20 +237,32 @@ static short cur_width, cur_font, cur_size;
} \
}
-/* Set up the current port to the off-screen buffer unconditionally.
- This is for measurement functions that don't draw. */
-#define BeginSilent { \
+/* Set up the current port unconditionally. This is for functions that
+ don't draw (measurements and setting the graphport state).
+ Usage: BeginOffAlways / EndOffAlways
+ or BeginOffAlways / OnAlways / EndOffOnAlways
+ */
+#define BeginOffAlways { \
CGrafPtr _saveport_; \
GDHandle _savegdev_; \
GetGWorld (&_saveport_, &_savegdev_); \
LockPixels (GetGWorldPixMap (gworld)); \
SetGWorld ((CGrafPtr) gworld, NULL);
-#define EndSilent \
+#define EndOffAlways \
SetGWorld (_saveport_, _savegdev_); \
UnlockPixels (GetGWorldPixMap (gworld)); \
}
+#define OnAlways \
+ SetGWorld (_saveport_, _savegdev_); \
+ UnlockPixels (GetGWorldPixMap (gworld)); \
+ SetPort (winGraphics); \
+
+#define EndOffOnAlways \
+ SetPort ((GrafPtr) _saveport_); \
+}
+
/* Convert a red, green, or blue value from 8 bits to 16 bits. */
#define RGB8to16(x) ((x) | ((x) << 8))
@@ -284,7 +296,7 @@ static void gr_check_open (void)
in one major GC cycle. The GC will speed up to match this allocation
speed.
*/
-#define Max_image_mem 1000000 /* XXX Should use user pref. */
+#define Max_image_mem 1000000 /*FIXME Should use user pref. */
#define Transparent (-1)
@@ -425,12 +437,11 @@ value gr_sigio_handler (value unit) /* Not used on MacOS */
value gr_synchronize (value unit)
{
#pragma unused (unit)
- GrafPtr port;
+ GrafPtr saveport;
- GetPort (&port);
- SetPort (winGraphics);
+ PushWindowPort (winGraphics);
GraphUpdate ();
- SetPort (port);
+ PopPort;
return Val_unit;
}
@@ -480,11 +491,11 @@ value gr_set_color (value vrgb)
fgcolor.red = RGB8to16 ((rgb >> 16) & 0xFF);
fgcolor.green = RGB8to16 ((rgb >> 8) & 0xFF);
fgcolor.blue = RGB8to16 (rgb & 0xFF);
- BeginOff
+ BeginOffAlways
RGBForeColor (&fgcolor);
- On
+ OnAlways
RGBForeColor (&fgcolor);
- EndOffOn
+ EndOffOnAlways
return Val_unit;
}
@@ -494,9 +505,9 @@ value gr_plot (value vx, value vy)
gr_check_open ();
BeginOff
- SetCPixel (Bx (x), By (y+1), &fgcolor);
+ SetCPixel (Bx (x), By (y) - 1, &fgcolor);
On
- SetCPixel (Wx (x), Wy (y+1), &fgcolor);
+ SetCPixel (Wx (x), Wy (y) - 1, &fgcolor);
EndOffOn
return Val_unit;
}
@@ -508,9 +519,9 @@ value gr_point_color (value vx, value vy)
gr_check_open ();
if (x < 0 || x >= w0 || y < 0 || y >= h0) return Val_long (-1);
- BeginSilent
- GetCPixel (Bx (x), By (y+1), &c);
- EndSilent
+ BeginOffAlways
+ GetCPixel (Bx (x), By (y) - 1, &c);
+ EndOffAlways
return Val_long (((c.red & 0xFF00) << 8)
| (c.green & 0xFF00)
| ((c.blue & 0xFF00) >> 8));
@@ -521,11 +532,6 @@ value gr_moveto (value vx, value vy)
XY;
gr_check_open ();
- BeginOff
- MoveTo (Bx (x), By (y));
- On
- MoveTo (Wx (x), Wy (y));
- EndOffOn
cur_x = x; cur_y = y;
return Val_unit;
}
@@ -549,12 +555,15 @@ value gr_current_y (value unit)
value gr_lineto (value vx, value vy)
{
XY;
+ int delta = cur_width / 2;
gr_check_open ();
BeginOff
- LineTo (Bx (x), By (y));
+ MoveTo (Bx (cur_x) - delta, By (cur_y) - delta);
+ LineTo (Bx (x) - delta, By (y) - delta);
On
- LineTo (Wx (x), Wy (y));
+ MoveTo (Wx (cur_x) - delta, Wy (cur_y) - delta);
+ LineTo (Wx (x) - delta, Wy (y) - delta);
EndOffOn
cur_x = x; cur_y = y;
return Val_unit;
@@ -565,13 +574,15 @@ value gr_draw_rect (value vx, value vy, value vw, value vh)
XY;
long w = Long_val (vw), h = Long_val (vh);
Rect r;
+ int d1 = cur_width / 2;
+ int d2 = cur_width - d1;
gr_check_open ();
BeginOff
- SetRect (&r, Bx (x), By (y+h), Bx (x+w), By (y));
+ SetRect (&r, Bx (x) - d1, By (y+h) - d1, Bx (x+w) + d2, By (y) + d2);
FrameRect (&r);
On
- SetRect (&r, Wx (x), Wy (y+h), Wx (x+w), Wy (y));
+ SetRect (&r, Wx (x) - d1, Wy (y+h) - d1, Wx (x+w) + d2, Wy (y) + d2);
FrameRect (&r);
EndOffOn
return Val_unit;
@@ -591,13 +602,15 @@ value gr_draw_arc_nat (value vx, value vy, value vrx, value vry, value va1,
long a1 = Long_val (va1), a2 = Long_val (va2);
Rect r;
long qda1 = 90 - a1, qda2 = 90 - a2;
+ int d1 = cur_width / 2;
+ int d2 = cur_width - d1;
gr_check_open ();
BeginOff
- SetRect (&r, Bx (x-rx), By (y+ry), Bx (x+rx), By (y-ry));
+ SetRect (&r, Bx(x-rx) - d1, By(y+ry) - d1, Bx(x+rx) + d2, By(y-ry) + d2);
FrameArc (&r, qda1, qda2 - qda1);
On
- SetRect (&r, Wx (x-rx), Wy (y+ry), Wx (x+rx), Wy (y-ry));
+ SetRect (&r, Wx(x-rx) - d1, Wy(y+ry) - d1, Wx(x+rx) + d2, Wy(y-ry) + d2);
FrameArc (&r, qda1, qda2 - qda1);
EndOffOn
return Val_unit;
@@ -609,11 +622,11 @@ value gr_set_line_width (value vwidth)
if (width == 0) width = 1;
gr_check_open ();
- BeginOff
+ BeginOffAlways
PenSize (width, width);
- On
+ OnAlways
PenSize (width, width);
- EndOffOn
+ EndOffOnAlways
cur_width = width;
return Val_unit;
}
@@ -640,8 +653,8 @@ value gr_fill_poly (value vpoints)
long i, n = Wosize_val (vpoints);
PolyHandle p;
- #define Bxx(i) Bx (Field (Field (vpoints, (i)), 0))
- #define Byy(i) By (Field (Field (vpoints, (i)), 1))
+ #define Bxx(i) Bx (Int_val (Field (Field (vpoints, (i)), 0)))
+ #define Byy(i) By (Int_val (Field (Field (vpoints, (i)), 1)))
gr_check_open ();
if (n < 1) return Val_unit;
@@ -686,19 +699,34 @@ value gr_fill_arc_nat (value vx, value vy, value vrx, value vry, value va1,
return Val_unit;
}
-value gr_draw_char (value vchr)
+static void draw_text (char *txt, unsigned long len)
{
- char c = Int_val (vchr);
+ FontInfo info;
+ unsigned long w;
+
+ if (len > 32767) len = 32767;
+
+ BeginOffAlways
+ GetFontInfo (&info);
+ w = TextWidth (txt, 0, len);
+ EndOffAlways
gr_check_open ();
BeginOff
- DrawChar (c);
+ MoveTo (Bx (cur_x), By (cur_y) - info.descent);
+ DrawText (txt, 0, len);
On
- DrawChar (c);
+ MoveTo (Wx (cur_x), Wy (cur_y) - info.descent);
+ DrawText (txt, 0, len);
EndOffOn
- BeginSilent
- cur_x += CharWidth (c);
- EndSilent
+ cur_x += w;
+}
+
+value gr_draw_char (value vchr)
+{
+ char c = Int_val (vchr);
+
+ draw_text (&c, 1);
return Val_unit;
}
@@ -707,16 +735,7 @@ value gr_draw_string (value vstr)
mlsize_t len = string_length (vstr);
char *str = String_val (vstr);
- gr_check_open ();
- if (len > 32767) len = 32767;
- BeginOff
- DrawText (str, 0, len);
- On
- DrawText (str, 0, len);
- EndOffOn
- BeginSilent
- cur_x = TextWidth (str, 0, len);
- EndSilent
+ draw_text (str, len);
return Val_unit;
}
@@ -728,11 +747,11 @@ value gr_set_font (value vfontname)
gr_check_open ();
CopyCStringToPascal (String_val (vfontname), pfontname);
GetFNum (pfontname, &fontnum);
- BeginOff
+ BeginOffAlways
TextFont (fontnum);
- On
+ OnAlways
TextFont (fontnum);
- EndOffOn
+ EndOffOnAlways
cur_font = fontnum;
return Val_unit;
}
@@ -742,11 +761,11 @@ value gr_set_text_size (value vsz)
short sz = Int_val (vsz);
gr_check_open ();
- BeginOff
+ BeginOffAlways
TextSize (sz);
- On
+ OnAlways
TextSize (sz);
- EndOffOn
+ EndOffOnAlways
cur_size = sz;
return Val_unit;
}
@@ -759,11 +778,11 @@ value gr_text_size (value vstr)
FontInfo info;
long w, h;
- BeginSilent
+ BeginOffAlways
GetFontInfo (&info);
w = TextWidth (str, 0, len);
h = info.ascent + info.descent;
- EndSilent
+ EndOffAlways
Field (result, 0) = Val_long (w);
Field (result, 1) = Val_long (h);
return result;
diff --git a/otherlibs/bigarray/Makefile.Mac.depend b/otherlibs/bigarray/Makefile.Mac.depend
index b694877ff..21307c037 100644
--- a/otherlibs/bigarray/Makefile.Mac.depend
+++ b/otherlibs/bigarray/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:24:12 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:23:44 on 24 avr 2000 by MakeDepend
:bigarray_stubs.c.x Ä ¶
:bigarray_stubs.c ¶
@@ -36,7 +36,7 @@
"{CIncludes}"WCharTDef.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:24:14 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:23:46 on 24 avr 2000 by MakeDepend
:bigarray_stubs.c.o Ä ¶
:bigarray_stubs.c ¶
diff --git a/otherlibs/macosunix/Makefile.Mac.depend b/otherlibs/macosunix/Makefile.Mac.depend
index 10d95de8c..54c7d62ec 100644
--- a/otherlibs/macosunix/Makefile.Mac.depend
+++ b/otherlibs/macosunix/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:24:57 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:24 on 24 avr 2000 by MakeDepend
:accept.c.x Ä ¶
:accept.c ¶
@@ -433,7 +433,7 @@
"{CIncludes}"MixedMode.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:04 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:31 on 24 avr 2000 by MakeDepend
:accept.c.o Ä ¶
:accept.c ¶
diff --git a/otherlibs/num/Makefile.Mac.depend b/otherlibs/num/Makefile.Mac.depend
index d21c4558e..53b2dd744 100644
--- a/otherlibs/num/Makefile.Mac.depend
+++ b/otherlibs/num/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:09 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:38 on 24 avr 2000 by MakeDepend
:nat_stubs.c.x Ä ¶
:nat_stubs.c ¶
@@ -11,7 +11,7 @@
"{CIncludes}"MixedMode.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:11 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:40 on 24 avr 2000 by MakeDepend
:nat_stubs.c.o Ä ¶
:nat_stubs.c ¶
diff --git a/otherlibs/str/Makefile.Mac.depend b/otherlibs/str/Makefile.Mac.depend
index 2942c5526..3000c06a0 100644
--- a/otherlibs/str/Makefile.Mac.depend
+++ b/otherlibs/str/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:17 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:46 on 24 avr 2000 by MakeDepend
:strstubs.c.x Ä ¶
:strstubs.c ¶
@@ -13,7 +13,7 @@
"{CIncludes}"MixedMode.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:19 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:48 on 24 avr 2000 by MakeDepend
:strstubs.c.o Ä ¶
:strstubs.c ¶
diff --git a/otherlibs/systhreads/Makefile.Mac.depend b/otherlibs/systhreads/Makefile.Mac.depend
index ec29ca1c3..d58e475f9 100644
--- a/otherlibs/systhreads/Makefile.Mac.depend
+++ b/otherlibs/systhreads/Makefile.Mac.depend
@@ -1,5 +1,5 @@
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:27 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:24:56 on 24 avr 2000 by MakeDepend
:posix.c.x Ä ¶
:posix.c ¶
@@ -52,7 +52,7 @@
"{CIncludes}"DateTimeUtils.h
#*** Dependencies: Cut here ***
-# These dependencies were produced at 21:25:33 on 17 avr 2000 by MakeDepend
+# These dependencies were produced at 14:25:00 on 24 avr 2000 by MakeDepend
:posix.c.o Ä ¶
:posix.c ¶