1(* ************************************************************************ *)
2(*                                                                          *)
3(* OCAMAKE - OCaml Automatic compilation                                    *)
4(*      (c)2002 Nicolas Cannasse                                            *)
5(*      (c)2002 Motion-Twin                                                 *)
6(*                                                                          *)
7(* Last version : http://tech.motion-twin.com                               *)
8(*                                                                          *)
9(* ************************************************************************ *)
10open Unix
11open Printf
12open Arg
13
14type compile_mode =
15	| CM_DEFAULT
16	| CM_BYTE
17	| CM_OPT
18
19type file_ext =
20	| ML | MLI | MLL | MLY
21	| CMO | CMX | CMA | CMXA
22	| DLL | SO | EXE | LIB
23	| CMI | O | OBJ | A
24
25type file = {
26	name : string;
27	ext : file_ext;
28	target : string;
29	deps : string list;
30}
31
32(* ************************************************************************ *)
33(* GLOBALS *)
34
35let verbose = ref false (* print command calls in verbose mode *)
36let project_name = ref None (* for VC++ DSP *)
37let error_process = ref false (* VC++ error message processing *)
38let chars_process = ref false (* replace chars range in errors by file data *)
39
40(* ************************************************************************ *)
41(* USEFUL FUNCTIONS *)
42
43let if_some f opt def =
44	match opt with
45	| None -> def
46	| Some v -> f v
47
48let print str = print_endline str; flush Pervasives.stdout
49
50let (???) file =
51	failwith ("Don't know what to do with file " ^ file)
52
53let str_suffix = function
54	| ML -> "ml" | MLI -> "mli" | MLL -> "mll" | MLY -> "mly" | CMO -> "cmo"
55	| CMX -> "cmx" | CMA -> "cma" | CMXA -> "cmxa" | DLL -> "dll" | SO -> "so"
56	| EXE -> "exe" | CMI -> "cmi" | O -> "o" | A -> "a" | OBJ -> "obj"
57	| LIB -> "lib"
58
59let unescape file =
60	let l = String.length file in
61	if l >= 2 && file.[0] = '"' && file.[l-1] = '"' then String.sub file 1 (l-2) else file
62
63let extension file =
64	let rsplit_char str ch =
65		let p = String.rindex str ch in
66		let len = String.length str in
67		(String.sub str 0 p, String.sub str (p + 1) (len - p - 1))
68	in
69	let file = unescape file in
70	let s = try snd(rsplit_char file '.') with Not_found -> "" in
71	String.uppercase s
72
73let (+!) file suff =
74	let base = Filename.chop_extension file in
75	base ^ "." ^ str_suffix suff
76
77let filter_all_in func ic =
78	let rec treat acc =
79	try
80		match func (input_line ic) with
81		| None -> treat acc
82		| Some data -> treat (data :: acc)
83	with
84		End_of_file -> close_in ic; acc
85	in
86	List.rev (treat [])
87
88let rec remove_duplicates = function
89	| [] -> []
90	| item :: q when List.exists ((=) item) q -> remove_duplicates q
91	| item :: q -> item :: remove_duplicates q
92
93let file_time fname =
94	try (Unix.stat fname).st_mtime with Unix_error _ -> 0.
95
96let flatten = String.concat " "
97
98let escape str =
99	try
100		ignore(String.index str ' ');
101		"\"" ^ str ^ "\"";
102	with Not_found -> str
103
104let delete_file file =
105	try Sys.remove file with Sys_error _ -> ()
106
107let check_existence (ext,name) =
108	match ext with
109	| ML | MLI ->
110		if not (Sys.file_exists name) then
111			failwith ("No such file : '"^(escape name)^"'")
112	| _ -> ()
113		(* Others files can be found in Ocaml stdlib or
114		   user -I paths *)
115
116exception Found_pos of int
117
118let print_errors output msg =
119	let split str sep =
120		let find_sub str sub =
121			let len = String.length sub in
122			try
123				for i = 0 to String.length str - len do
124					if String.sub str i len = sub then raise (Found_pos i);
125				done;
126				raise Not_found
127			with Found_pos i -> i
128		in
129		let p = find_sub str sep in
130		let len = String.length sep in
131		let slen = String.length str in
132		(String.sub str 0 p, String.sub str (p + len) (slen - p - len))
133	in
134	let process_chars file chars line =
135		let cmin, cmax = split chars "-" in
136		let cmin, cmax = int_of_string cmin, int_of_string cmax in
137		if cmax > cmin then begin
138			let f = open_in file in
139			for i = 1 to line-1 do ignore(input_line f) done;
140			seek_in f ((pos_in f)+cmin);
141			let s = String.create (cmax - cmin) in
142			ignore(input f s 0 (cmax - cmin));
143			prerr_endline (try
144					(String.sub s 0 (String.index s '\n'))^"..."
145				with
146					Not_found -> s);
147		end
148	in
149	let printer =
150		(match !error_process , !chars_process with
151		| true , _ -> (function line ->
152			try
153				let data, chars = split line ", characters " in
154				let data, lnumber = split data "\", line " in
155				let _, file = split data "File \"" in
156				prerr_string (file ^ "(" ^ lnumber ^ ") : ");
157				let chars, _ = split chars ":" in
158				if !chars_process then
159					process_chars file chars (int_of_string lnumber);
160 			with
161				Not_found ->
162					prerr_endline line)
163		| false , true -> (function line ->
164			try
165				let edata, chars = split line ", characters " in
166				let data, lnumber = split edata "\", line " in
167				let _, file = split data "File \"" in
168				let chars, _ = split chars ":" in
169				prerr_string (edata^" : ");
170				if !chars_process then
171					process_chars file chars (int_of_string lnumber);
172 			with
173				Not_found ->
174					prerr_endline line)
175
176		| false , false ->
177		      prerr_endline)
178	in
179	List.iter printer output;
180	failwith msg
181
182let exec ?(stdout=false) ?(outfirst=false) cmd errmsg =
183	if !verbose then print cmd;
184	let pout, pin, perr = open_process_full cmd (Unix.environment()) in
185	let read = filter_all_in (fun s -> Some s) in
186	let data, edata =
187	(* this is made to prevent the program lock when one
188	   buffer is full and the process is waiting for us
189	   to read it before exiting... while we're reading
190	   the other output buffer ! *)
191	(if outfirst then
192		let d = read pout in
193		let ed = read perr in
194		d,ed
195	else
196		let ed = read perr in
197		let d = read pout in
198		d,ed) in
199	match close_process_full (pout, pin, perr) with
200	| WEXITED 0 -> data,edata
201	| WEXITED exitcode -> print_errors (if stdout then edata @ data else edata) errmsg
202	| _ -> failwith "Build aborted by signal"
203
204(* ************************************************************************ *)
205(* DEPENDENCIES *)
206
207let line_regexp = Str.regexp "^\\([0-9A-Za-z:_\\./\\\\-]+\\.cm[oi]\\):\\( .*\\)$"
208let dep_regexp = Str.regexp " \\([0-9A-Za-z:_\\./\\\\-]+\\.cm[oi]\\)"
209
210let build_graph opt paramlist files =
211	let srcfiles = List.filter (fun (e,_) ->
212		match e with
213		| ML | MLI -> true
214		| _ -> false) files in
215	let get_name (_,f) = escape f in
216	let file_names = flatten (List.map get_name srcfiles) in
217	let params = flatten paramlist in
218	let command = sprintf "ocamldep %s %s" params file_names in
219	let output,_ = exec command "Failed to make dependencies" ~outfirst:true in
220	let data = String.concat "\n" output in
221	let data = Str.global_replace (Str.regexp "\\\\\r\n") "" data in (* win *)
222	let data = Str.global_replace (Str.regexp "\\\\\n") "" data in (* unix *)
223	let rec get_deps data p =
224		try
225			let newp = Str.search_forward dep_regexp data p in
226			let file = Str.matched_group 1 data in
227			if opt && extension file = "CMO" then
228				(file +! CMX)::(get_deps data (newp+1))
229			else
230				file::(get_deps data (newp+1))
231		with
232			Not_found -> []
233	in
234	let rec get_lines p =
235		try
236			let newp = Str.search_forward line_regexp data p in
237			let file = Str.matched_group 1 data in
238			let lines = get_deps (Str.matched_group 2 data) 0 in
239			(Filename.basename file,lines)::(get_lines (newp+1))
240		with
241			Not_found -> []
242	in
243	let lines = get_lines 0 in
244	let init_infos (ext,fname) =
245		let deptarget = Filename.basename (match ext with
246			| ML ->  fname +! CMO
247			| MLI -> fname +! CMI
248			| _ -> fname) in
249		let target = (match ext with
250			| ML -> fname +! (if opt then CMX else CMO)
251			| MLI -> fname +! CMI
252			| _ -> fname) in
253		{
254			name = fname;
255			ext = ext;
256			target = target;
257			deps =
258				(try
259					snd (List.find (fun (n,_) -> n = deptarget) lines)
260				with
261					Not_found -> []);
262		}
263	in
264	let deps = List.map init_infos files in
265	match !verbose with
266	| false -> deps
267	| true ->
268		let print_dep d =
269			let dl = String.concat " " (List.map Filename.basename d.deps) in
270			printf "%s: %s\n" (Filename.basename d.target) dl;
271		in
272		List.iter print_dep deps;
273		deps
274
275let rec graph_topological_sort all g priority acc =
276	let has_dep where dep =
277		List.exists (fun f -> Filename.basename f.target =
278							Filename.basename dep) where
279	in
280	let modified a b = (file_time a) < (file_time b) in
281	let is_free file = not(List.exists (has_dep g) file.deps) in
282	let rec has_priority = function
283		| [] -> raise Not_found
284		| x :: l ->
285			try
286				List.find (fun f -> x = (Filename.basename f.name)) g
287			with
288				Not_found -> has_priority l
289	in
290	let to_build file =
291		all || (* rebuild all *)
292		List.exists (has_dep acc) file.deps || (* a dep is rebuild *)
293		List.exists (modified file.target) file.deps || (* dep modified *)
294		(file_time file.target) < (file_time file.name) (* is modified *)
295	in
296	match g with
297	| [] -> acc
298	| _ ->
299		let free,g = List.partition is_free g in
300		match free with
301		| [] ->
302			(try
303				let free = has_priority priority in
304				let g = List.filter ((<>) free) g in
305				if to_build free then
306					graph_topological_sort all g priority (acc@[free])
307				else
308					graph_topological_sort all g priority acc;
309			with Not_found ->
310				List.iter (fun f -> prerr_endline f.name) g;
311				failwith "Cycle detected in file dependencies !")
312		| _ ->
313			let to_build = List.filter to_build free in
314			graph_topological_sort all g priority (acc@to_build)
315
316(* ************************************************************************ *)
317(* COMPILATION *)
318
319let compile ?(precomp=false) opt paramlist f =
320	try
321		let command = (match f.ext with
322		| ML | MLI ->
323			let params = flatten paramlist in
324			let compiler = (if opt then "ocamlopt" else "ocamlc") in
325			sprintf "%s -c %s %s" compiler params (escape f.name)
326		| MLL when precomp -> "ocamllex " ^ (escape f.name)
327		| MLY when precomp -> "ocamlyacc " ^ (escape f.name)
328		| _ -> raise Exit) in
329		print (Filename.basename (unescape f.name));
330		let stdout,stderr = exec command "Build failed" in
331		try
332			print_errors (stderr@stdout) "";
333		with
334			Failure _ -> ()
335	with
336		Exit -> ()
337
338let pre_compile all (ext,name) =
339	match ext with
340	| MLL | MLY ->
341		let time = file_time name in
342		if time = 0. then failwith ("No such file : "^(escape name));
343		if all || (file_time (name +! ML)) < time then
344			compile ~precomp:true false [] {
345				name = name;
346				ext = ext;
347				deps = [];
348				target = "";
349			}
350	| _ -> () (* other files type does not need pre-compilation *)
351
352let clean_targets opt acc (ext,name) =
353	match ext with
354	| MLY ->
355		(name +! ML) :: (name +! MLI) :: acc
356	| MLL ->
357		(name +! ML) :: acc
358	| ML when opt ->
359		(name +! (if Sys.os_type = "Win32" then OBJ else O)) :: (name +! CMX) :: (name +! CMI) :: acc
360	| ML ->
361		(name +! CMO) :: (name +! CMI) :: acc
362	| MLI ->
363		(name +! CMI) :: acc
364	| _ ->
365		acc
366
367(*
368	In order to link, we need to order the CMO files.
369	We currently have a ML/MLI dependency graph (in fact, tree) generated
370	by ocamldep.
371
372	To build the CMO list, we are reducing the dep-tree into one graph merging
373	corresponding ML & MLI nodes. ML-ML edges are keeped, ML-MLI edges
374	become ML-ML edges only if they do not create a cycle in the reduced
375	graph.
376
377	Then we sort the graph using topological ordering.
378*)
379let graph_reduce opt g =
380	let ext = (if opt then CMX else CMO) in
381	let rec path_exists g a b =
382		if a = b then true else
383		try
384			let f = List.find (fun f -> f.target = a) g in
385			List.exists (fun d -> path_exists g d b) f.deps
386		with
387			Not_found -> false
388	in
389	let rec deps_reduce f g = function
390		| [] -> []
391		| dep::deps ->
392			match extension dep with
393			| "CMI" when not(path_exists g (dep +! ext) f.target) ->
394				(dep +! ext)::(deps_reduce f g deps)
395			| "CMO" | "CMX" ->
396				dep::(deps_reduce f g deps)
397			| _ -> deps_reduce f g deps
398	in
399	let rec do_reduce g acc =
400		match g with
401		| [] -> acc
402		| f::g' ->
403			let f = { f with deps = deps_reduce f (g@acc) f.deps } in
404			do_reduce g' (f::acc)
405	in
406	do_reduce g []
407
408let is_lib f = match f.ext with
409	| CMA | CMXA | CMO | CMX | DLL | SO | LIB | A | O | OBJ -> true
410	| _ -> false
411
412let link opt paramlist files priority output =
413	print "Linking...";
414	let sources = List.filter (fun f -> f.ext = ML) files in
415	let libs = List.filter is_lib files in
416	let sources = graph_topological_sort true (graph_reduce opt sources) priority [] in
417	let lparams = flatten (List.map (fun f -> escape f.name) libs) in
418	let sparams = flatten (List.map (fun f -> escape f.target) sources) in
419	let params = flatten paramlist in
420	let cc = (if opt then "ocamlopt" else "ocamlc") in
421	let cmd = sprintf "%s %s %s %s -o %s" cc params lparams sparams output in
422	ignore(exec ~stdout:true cmd "Linking failed")
423
424(* ************************************************************************ *)
425(* FILE PROCESSING *)
426
427let dsp_get_files dsp_file =
428	let get_file line =
429		if String.length line > 7 && String.sub line 0 7 = "SOURCE=" then
430			Some (unescape (String.sub line 7 (String.length line-7)))
431		else
432			None
433	in
434	filter_all_in get_file (open_in dsp_file)
435
436let vcproj_get_files vcp_file =
437	let get_file line =
438		let len = String.length line in
439		let p = ref 0 in
440		while !p < len && (line.[!p] = ' ' || line.[!p] = '\t') do
441			incr p;
442		done;
443		let line = String.sub line !p (len - !p) in
444		if String.length line > 13 && String.sub line 0 13 = "RelativePath=" then begin
445			let str = String.sub line 14 (String.length line - 15) in
446			Some (unescape str)
447		end else
448			None
449	in
450	filter_all_in get_file (open_in vcp_file)
451
452let rec list_files errors file =
453	match extension file with
454	| "ML" -> [(ML,file)]
455	| "MLI" -> [(MLI,file)]
456	| "VCPROJ" ->
457		project_name := Some (Filename.basename file);
458		error_process := true;
459		chars_process := true;
460		List.concat (List.map (list_files false) (vcproj_get_files file))
461	| "DSP" ->
462		project_name := Some (Filename.basename file);
463		error_process := true;
464		chars_process := true;
465		List.concat (List.map (list_files false) (dsp_get_files file))
466	| "CMA" -> [(CMA,file)]
467	| "CMXA" -> [(CMXA,file)]
468	| "CMX" -> [(CMX,file)]
469	| "CMO" -> [(CMO,file)]
470	| "DLL" -> [(DLL,file)]
471	| "LIB" -> [(LIB,file)]
472	| "A" -> [(A,file)]
473	| "O" -> [(O,file)]
474	| "OBJ" -> [(OBJ,file)]
475	| "SO" -> [(SO,file)]
476	| "MLY" -> [(MLY,file);(ML,file +! ML);(MLI,file +! MLI)]
477	| "MLL" -> [(MLL,file);(ML,file +! ML)]
478	| _ -> if errors then ??? file else []
479
480let rec get_compile_mode cm = function
481	| [] -> cm
482	| (ext,name)::files ->
483		let error() = failwith "Mixed bytecode and native compilation files." in
484		match ext with
485		| ML | MLI | MLL | MLY | DLL | SO ->
486			get_compile_mode cm files
487		| CMA | CMO ->
488			if cm = CM_OPT then error() else get_compile_mode CM_BYTE files
489		| CMXA | CMX | A | O | OBJ | LIB ->
490			if cm = CM_BYTE then error() else get_compile_mode CM_OPT files
491		| EXE | CMI ->
492			assert false
493
494let rec get_output_file islib cm =
495	match !project_name,islib,cm with
496	| None, _ , _ -> None
497	| Some name,false,_ -> Some (name +! EXE)
498	| Some name,true,CM_OPT -> Some (name +! CMXA)
499	| Some name,true,_ -> Some (name +! CMA)
500
501(* ************************************************************************ *)
502(* MAIN *)
503
504;;
505try
506
507let usage =
508	"OCAMAKE v1.4 - Copyright (C)2002-2005 Nicolas Cannasse"
509	^"\r\nLast version : http://tech.motion-twin.com" in
510let compile_mode = ref CM_DEFAULT in
511let compile_cma = ref false in
512let do_clean = ref false in
513let gen_make = ref false in
514let rebuild_all = ref false in
515let output_file = ref None in
516let preprocessor = ref None in
517let argfiles = ref [] in
518let paths = ref [] in
519let cflags = ref [] in
520let lflags = ref [] in
521let remf = ref [] in
522let priority = ref [] in
523let arg_spec = [
524  ("-all", Unit (fun () -> rebuild_all := true), ": rebuild all files");
525  ("-o", String (fun f -> output_file := Some f), "<file> : set output");
526  ("-a", Unit (fun () -> compile_cma := true), ": build a library");
527  ("-opt", Unit (fun () -> compile_mode := CM_OPT), ": native compilation");
528  ("-clean", Unit (fun () -> do_clean := true), ": delete intermediate files");
529  ("-I", String (fun p -> paths := p::!paths), "<path> : additional path");
530  ("-v", Unit (fun () -> verbose := true), ": turn on verbose mode");
531  ("-n", String (fun f -> remf := f::!remf),"<file>: don't compile this file");
532  ("-mak", Unit (fun () -> gen_make := true), ": generate Makefile");
533  ("-lp", String (fun f -> lflags := f::!lflags), "<p> : linker parameter");
534  ("-cp", String (fun f -> cflags := f::!cflags), "<p> : compiler parameter");
535  ("-pp", String (fun c -> preprocessor := Some c), "<cmd> : preprocessor");
536  ("-epp", Unit (fun() -> error_process := true), ": use MSVC error messages format");
537  ("-cpp", Unit (fun() -> chars_process := true), ": convert characters range in errors to file expression");
538  ("-g", Unit (fun () -> lflags := "-g"::!lflags; cflags := "-g"::!cflags), ": compile/link in debug mode");
539  ("-P", String (fun f -> priority := f::!priority), ": give linking priority to a file when linking ordering failed");
540] in
541Arg.parse arg_spec (fun arg -> argfiles := arg :: !argfiles) usage;
542let files = List.concat (List.map (list_files true) (List.rev !argfiles)) in
543let files = List.filter (fun (_,f) ->
544	let name = Filename.basename f in
545	not(List.exists (fun f -> Filename.basename f = name) !remf)) files in
546let compile_mode = get_compile_mode !compile_mode files in
547let output_file , compile_mode = (match !output_file with
548	| None -> get_output_file !compile_cma compile_mode , compile_mode
549	| Some file ->
550		match extension file , compile_mode with
551		| "CMA" , CM_OPT
552		| "CMXA", CM_BYTE -> failwith "Mixed bytecode and native compilation files."
553		| "CMA" , _ ->
554			compile_cma := true;
555			Some file , CM_BYTE
556		| "CMXA" , _ ->
557			compile_cma := true;
558			Some file , CM_OPT
559		| _ , _ ->
560			Some file , compile_mode)
561in
562let opt = (compile_mode = CM_OPT) in
563if !compile_cma then lflags := "-a"::!lflags;
564match files with
565  | [] -> Arg.usage arg_spec usage
566  | _ ->
567	let files = remove_duplicates files in
568	let get_path (_,f) = "-I " ^ escape (Filename.dirname f) in
569	let paths = List.map (fun p -> "-I " ^ (escape p)) !paths in
570	let paths = remove_duplicates (paths@(List.map get_path files)) in
571	let p4param = if_some (fun cmd -> "-pp " ^ (escape cmd)) !preprocessor "" in
572	match !do_clean,!gen_make with
573	| true,true ->
574		failwith "Cannot have -mak & -clean at the same time"
575	| false,false ->
576		if_some delete_file output_file ();
577		List.iter (pre_compile !rebuild_all) files;
578		List.iter check_existence files;
579		let g = build_graph opt (p4param::paths) files in
580		let files = graph_topological_sort !rebuild_all g [] [] in
581		List.iter (compile opt (!cflags @ p4param::paths)) files;
582		if_some (link opt (!lflags @ paths) g (List.rev !priority)) output_file ();
583		print "Done";
584	| true,false ->
585		print "Cleaning...";
586		if_some delete_file output_file ();
587		let to_clean = List.fold_left (clean_targets opt) [] files in
588		List.iter delete_file to_clean;
589		if opt && !compile_cma then
590			if_some (fun f -> delete_file (f +! (if Sys.os_type = "Win32" then LIB else A))) output_file ();
591	| false,true ->
592		List.iter (pre_compile !rebuild_all) files;
593		let g = build_graph opt (p4param::paths) files in
594		let out = open_out "Makefile" in
595		let fprint s = output_string out (s^"\n") in
596		let genmak f =
597			let ext = if opt then CMX else CMO in
598			match f.ext with
599			| MLL ->
600				fprint ((f.name +! ext)^": "^(f.name +! ML)^"\n")
601			| MLY ->
602				fprint ((f.name +! ext)^": "^(f.name +! ML)^"\n");
603				fprint ((f.name +! CMI)^": "^(f.name +! ML)^" "^(f.name +! MLI)^"\n")
604			| _ when f.deps <> [] ->
605				fprint (f.target^": "^(flatten f.deps)^"\n")
606			| _ ->
607				()
608		in
609		let compiles = graph_topological_sort true g [] [] in
610		let libs = List.filter is_lib compiles in
611		let cmos = List.filter (fun f -> f.ext = ML) compiles in
612		fprint "# Makefile generated by OCamake ";
613		fprint "# http://tech.motion-twin.com";
614		fprint ".SUFFIXES : .ml .mli .cmo .cmi .cmx .mll .mly";
615		fprint "";
616		fprint ("CFLAGS="^(flatten (!cflags @ p4param::paths)));
617		fprint ("LIBS="^(flatten (List.map (fun f -> f.name) libs)));
618		let targets = flatten (List.map (fun f -> f.target) cmos) in
619		(match output_file with
620		| None ->
621			fprint "";
622			fprint ("all: "^targets^"\n");
623		| Some out ->
624			fprint ("LFLAGS= -o "^out^" "^(flatten (!lflags @ paths)));
625			fprint "";
626			fprint ("all: "^out^"\n");
627			fprint (out^": "^targets);
628			(* I need to reuse the list of targets since $^ is for Make and $** for NMake *)
629			fprint ("\t"^(if opt then "ocamlopt" else "ocamlc")^" $(LFLAGS) $(LIBS) "^targets^"\n"));
630		List.iter genmak g;
631		fprint "";
632		fprint "clean:";
633		let cleanfiles = flatten (List.fold_left (clean_targets opt) [] files) in
634		if_some (fun o ->
635				fprint ("\trm -f "^o);
636				if opt && !compile_cma then fprint ("\trm -f "^(o +! LIB)^" "^(o +! A));
637			) output_file ();
638		fprint ("\trm -f "^cleanfiles);
639		fprint "";
640		fprint "wclean:";
641		if_some (fun o ->
642				fprint ("\t-@del "^o^" 2>NUL");
643				if opt && !compile_cma then fprint ("\t-@del "^(o +! LIB)^" "^(o +! A)^" 2>NUL");
644		) output_file ();
645		fprint ("\t-@del "^cleanfiles^" 2>NUL");
646		fprint "";
647		fprint "# SUFFIXES";
648		fprint ".ml.cmo:\n\tocamlc $(CFLAGS) -c $<\n";
649		fprint ".ml.cmx:\n\tocamlopt $(CFLAGS) -c $<\n";
650		fprint ".mli.cmi:\n\tocamlc $(CFLAGS) $<\n";
651		fprint ".mll.ml:\n\tocamllex $<\n";
652		fprint ".mly.ml:\n\tocamlyacc $<\n";
653		close_out out
654with
655	Failure msg ->
656		Pervasives.flush Pervasives.stdout;
657		prerr_endline msg;
658		Pervasives.flush Pervasives.stderr;
659		exit 1;
660
661(* ************************************************************************ *)
662