2 let (<|) = fun f g x -> f (g x)
3 and (|>) = fun f g x -> g (f x)
13 | ' '|'\n'|'\r'|'\t' -> true
23 ~(next:string -> int -> int -> (int * int))
24 ~(sub:acc:'acc -> skip: int -> string -> int -> int -> 'acc)
27 and siz = String.length string
30 while !bgn < siz || !last_skip <> 0 do
32 let keep, skip = next string pos (siz - pos) in
33 let inc = keep + skip in
34 assert (inc <> 0 || (inc = 0 && !last_skip <> 0));
35 acc := sub ~acc:!acc ~skip string pos keep;
43 ~sub: (fun ~acc ~skip string pos siz ->
44 let pos = String.length string - pos - siz in
45 String.sub string pos siz::acc)
46 ~next: (fun string pos siz ->
48 and pos = String.length string - pos - 1 in
49 while let keep = !keep
51 && not (char (String.unsafe_get string (pos - keep)))
53 (!keep, if !keep = siz then 0 else 1))
54 let char_with_separators_glued
57 ~sub: (fun ~acc ~skip string pos siz ->
58 let pos = String.length string - pos - siz in
59 let acc = String.sub string pos siz::acc in
61 then String.sub string (pos - skip) skip::acc
63 ~next: (fun string pos siz ->
66 and pos = String.length string - pos - 1 in
67 while let keep = !keep
69 && not (char (String.unsafe_get string (pos - keep)))
73 and siz = siz - keep in
74 while let skip = !skip
76 && char (String.unsafe_get string (pos - skip))
83 let len = String.length string in
88 match String.unsafe_get string (pred curr) with
89 | ' '|'\n'|'\r'|'\t' -> loop (pred curr)
90 | _ when curr = len -> string
91 | _ -> String.sub string 0 curr
96 let string = copy string in
97 for pos = 0 to pred (length string)
98 do match unsafe_get string pos with
99 | 'a'..'z' | 'A'..'Z' | '_' -> ()
100 | '0'..'9' when pos > 0 -> ()
101 | _ -> unsafe_set string pos '_'
106 let string = copy string in
107 for pos = 0 to min 0 (pred (length string))
108 do match unsafe_get string pos with
109 | 'a'..'z' | 'A'..'Z' | '_' -> ()
110 | _ -> unsafe_set string pos '_'
117 let (//) = Filename.concat
119 match Sys.os_type with
129 Pervasives.prerr_endline
130 ("File.rm: " ^ Printexc.to_string exn);
133 = fun ?(prefix="tmp") ?(suffix="tmp") fct ->
134 let (file, chan) = Filename.open_temp_file prefix suffix in
139 try let t = fct ~file ~chan in clean (); t
140 with exn -> clean (); raise exn
145 { close : unit -> unit
146 ; format : 'a. ('a, Pervasives.out_channel, unit) format -> 'a
151 { close = Pervasives.ignore
152 ; format = (fun format -> Printf.ifprintf Pervasives.stderr format)
155 let chan = Pervasives.open_out file in
156 { close = (fun _ -> Pervasives.close_out chan)
157 ; format = (fun format -> Printf.fprintf chan format)
165 = String.Split.char ((=) Path.char)
168 try split (Sys.getenv name)
173 try Some (Sys.getenv name)
174 with Not_found -> None
180 let self = Sys.argv.(0)
181 let c = ref (self^".h")
182 and caml = ref (self^".ml")
183 and camlpp = ref (self^".mlp")
184 and make = ref (self^".make")
185 and log = ref (self^".log")
197 and caml = !Param.caml
198 and camlpp = !Param.camlpp
199 and make = !Param.make
200 and log = !Param.log in
203 and caml = Out.t caml
204 and camlpp = Out.t camlpp
205 and make = Out.t make
206 and c_def = String.macrofy c in
213 if Sys.file_exists log
215 let t = fct {c=c; caml=caml; camlpp=camlpp; make=make; log=log} in
235 = fun ~glob:{Glob.c=c; caml=caml; camlpp=camlpp; make=make} name bool ->
241 c .Out.format "#define %s\n" name;
242 caml .Out.format "let _%s = true\n" name;
243 camlpp .Out.format "DEFINE %s\n" name;
244 make .Out.format "%s := true\n" name
246 c .Out.format "#undef %s\n" name;
247 caml .Out.format "let _%s = false\n" name;
248 camlpp .Out.format "(* DEFINE %s *)\n" name;
249 make .Out.format "%s := \n" name
251 = fun ~glob:{Glob.c=c; caml=caml; camlpp=camlpp; make=make} name string ->
255 c .Out.format "#define %s = %S\n" name string;
256 caml .Out.format "let _%s = %S\n" name string;
257 camlpp .Out.format "DEFINE %s = %S\n" name string;
258 make .Out.format "%s := \"%s\"\n" name string
268 = fun ~glob:{Glob.log=log} string ->
272 let log = Pervasives.open_out_gen
273 [Open_wronly; Open_append; Open_creat; Open_text] 0o660 log in
274 Pervasives.output_string log string;
275 Pervasives.close_out log;
283 Log.t ~glob (Printf.sprintf "$ %s\n" string);
286 if 0 = Sys.command string
290 match glob.Glob.log with
295 string (Filename.quote log))
296 let buffer_size = ref 2048
297 exception Exit of int * string
302 Log.t ~glob (Printf.sprintf "$ %s\n" string);
305 let size = !buffer_size in
306 let chan = Unix.open_process_in cmd
307 and buf = Buffer.create size
308 and string = String.create size
311 read := Pervasives.input chan string 0 size;
312 Buffer.add_substring buf string 0 !read
314 let string = Buffer.contents buf in
316 match Unix.close_process_in chan with
317 | Unix.WEXITED 0 -> string
318 | Unix.WEXITED int -> raise (Exit (int, string))
320 | Unix.WSTOPPED int ->
323 "command received signal %i: %s"
325 match glob.Glob.log with
327 | log -> Printf.ksprintf sh "{ %s ; } 2>&1" string)
333 let ocamlc = ref "ocamlfind ocamlc"
334 and ext_obj = ref ".o"
335 and ccomp_type = ref "cc"
346 (fun dir -> {inc=dir//"include"; lib=dir//"lib"})
362 [ List.map (fun dir -> {inc=dir; lib=dir//".."//"lib"})
363 (Env.Path.list "C_INCLUDE_PATH")
364 ; List.map (fun dir -> {inc=dir//".." //"include"; lib=dir})
365 (Env.Path.list "LIBRARY_PATH")
370 Log.t ~glob (Printf.sprintf "# searching for %s .. " h);
374 Log.t ~glob (Printf.sprintf "found NOTHING; \
375 you may use environment variables: \
376 C_INCLUDE_PATH and LIBRARY_PATH\n");
378 | {inc=inc; lib=lib}::list ->
379 match Sys.file_exists (inc//h) with
382 Log.t ~glob (Printf.sprintf "found include:%s lib:%s\n" inc lib);
383 Some {inc=inc; lib=lib}
391 = fun ~glob ~name ~default ->
394 ( Env.Path.list ("CFLAGS_" ^ name)
395 , Env.Path.list ("LIBS_" ^ name)
397 | (_::_ as opt), (_::_ as lib) -> (opt, lib)
399 let opt, lib = default () in
401 | (_::_ as opt), [] -> (opt, lib)
402 | [] , (_::_ as lib) -> (opt, lib)
403 | [] , [] -> (opt, lib)
404 | _ -> assert false in
405 let {Glob.make} = glob in
406 make.Out.format "CFLAGS_%s := %s\n" name (String.concat " " inc);
407 make.Out.format "LIBS_%s := %s\n" name (String.concat " " lib);
414 File.tmp ~prefix: "configure_ml_" ~suffix: ".ml"
416 Pervasives.output_string chan string;
417 Pervasives.close_out chan;
420 File.rm (Filename.chop_extension file ^ ".cmi");
421 File.rm (Filename.chop_extension file ^ ".cmo");
422 File.rm (Filename.chop_extension file ^ ".byte");
424 try let t = fct ~ml:file in clean (); t
425 with exn -> clean (); raise exn
432 File.tmp ~prefix: "configure_c_" ~suffix: ".c"
434 Pervasives.output_string chan string;
435 Pervasives.close_out chan;
438 File.rm (Filename.chop_extension file ^ !Param.ext_obj);
440 try let t = fct ~c:file in clean (); t
441 with exn -> clean (); raise exn
445 = fun ~glob (opt, lib) c ->
447 external t : unit -> unit = \"t\"\n\
451 (fun ~c -> Shell.t ~glob
452 "cd %s && %s -o %s -verbose -custom %s %s %s %s"
453 (Filename.quote (Filename.dirname c))
455 (Filename.quote ((Filename.chop_extension ml) ^ ".byte"))
456 (String.concat " " (List.map (fun t -> Printf.sprintf "-ccopt %s" (Filename.quote t)) opt))
457 (String.concat " " (List.map (fun t -> Printf.sprintf "-cclib %s" (Filename.quote t)) lib))
459 (Filename.quote ml)))
473 try Int (Pervasives.int_of_string string)
474 with Failure "int_of_string" -> String string)
475 (String.Split.char_with_separators_glued
476 ((not) <| Char.decimal) string)
482 | Int int -> Pervasives.string_of_int int
483 | String string -> string) t)
486 let string = String.t
501 | NOT (t) -> not (bool t)
502 | AND (t, tt) -> bool t && bool tt
503 | OR (t, tt) -> bool t || bool tt
504 | EQ (v, vv) -> v = vv
505 | LT (v, vv) -> v < vv
506 | LE (v, vv) -> v <= vv
507 | GT (v, vv) -> v > vv
508 | GE (v, vv) -> v >= vv
511 | NOT (t) -> Printf.sprintf "(not %s)" (string t)
512 | AND (t, tt) -> Printf.sprintf "(%s && %s)" (string t) (string tt)
513 | OR (t, tt) -> Printf.sprintf "(%s || %s)" (string t) (string tt)
514 | EQ (v, vv) -> Printf.sprintf "(%s = %s)" (String.t v) (String.t vv)
515 | LT (v, vv) -> Printf.sprintf "(%s < %s)" (String.t v) (String.t vv)
516 | LE (v, vv) -> Printf.sprintf "(%s <= %s)" (String.t v) (String.t vv)
517 | GT (v, vv) -> Printf.sprintf "(%s > %s)" (String.t v) (String.t vv)
518 | GE (v, vv) -> Printf.sprintf "(%s >= %s)" (String.t v) (String.t vv)
520 exception Constraint of t * Constraint.t
526 = fun ~glob ?(enable=true) ?(optional=false) ?(mem=ref None)
527 ~descr ?(info=fun _ -> "") ?(info_exn=fun _ -> "")
536 | false -> raise Check))
538 Log.t ~glob (Printf.sprintf "# checking %s\n" descr);
539 Trace.format "checking %s %!" descr;
540 let line = (String.make (45 - String.length descr) '.') in
543 Trace.format "%s skip\n%!" line;
544 Emit.bool ~glob macro enable;
547 match (try Some (test ~glob), Not_found
548 with exn -> None, exn) with
549 | Some t as option, _ ->
551 Trace.format "%s ok %s\n%!" line info;
552 Emit.bool ~glob macro true;
556 Trace.format "%s KO" line;
557 Emit.bool ~glob macro false;
561 Trace.format " (optional) %s\n%!" (info_exn exn);
564 Trace.format " (NOT optional) %s\n%!" (info_exn exn);
569 = fun ?optional ?enable ?(mem=ref None) ?(info_exn=fun _ -> "")
571 ?(constraint_=fun t -> Version.Constraint.EQ (t, t))
573 let old_mem = !mem in
574 match t ~glob ?optional ?enable ~mem ~descr ~macro
575 ~info: (fun t -> Printf.sprintf "(version %s)" (Version.string t))
577 | Version.Constraint (v, c) ->
578 Printf.sprintf "(version %s MUST satisfy: %s)"
580 (Version.Constraint.string c)
581 | exn -> info_exn exn)
583 let v = version ~glob in
584 let c = constraint_ v in
585 if not (Version.Constraint.bool c)
586 then raise (Version.Constraint (v, c))
589 | Some version as option ->
592 let version = Version.string version in
593 Emit.string ~glob (String.macrofy ("VERSION_" ^ macro)) version;
594 Emit.bool ~glob (String.macrofy ("VERSION_" ^ macro ^ "_" ^ version)) true;
606 { ocamlc : Version.t option
607 ; ocamlopt : Version.t option
610 and mem_ocamlc = ref None
611 and mem_ocamlopt = ref None
613 = fun ~glob ?optional
614 ?version_ocamlc ?version_ocamlopt
616 match Check.t ~glob ~descr: "ocamlfind"
617 ~macro: "HAVE_ocamlfind" ?optional ~mem
618 (Shell.t "ocamlfind printconf")
623 Check.Version.t ~glob ~descr: "ocamlc" ~macro: "OCAMLC"
624 ~optional: false ?constraint_:version_ocamlc ~mem: mem_ocamlc
625 (fun ~glob -> Version.t (String.chomp
626 (Shell.string ~glob "ocamlfind ocamlc -version"))) in
628 Check.Version.t ~glob ~descr: "ocamlopt" ~macro: "OCAMLOPT"
629 ~optional: true ?constraint_:version_ocamlopt ~mem: mem_ocamlopt
630 (fun ~glob -> Version.t (String.chomp
631 (Shell.string ~glob "ocamlfind ocamlopt -version"))) in
634 ; ocamlopt = ocamlopt
642 = fun ~glob: ({Glob.c=c; caml=caml; camlpp=camlpp; make=make} as glob)
643 ?optional ?enable ?mem ?version
645 assert (None <> Check.t () ~glob ~optional: false);
646 Check.Super.Version.t ~glob ?optional ?enable ?mem ?constraint_:version
647 ~descr: ("ocamlfind package " ^ name)
648 ~macro: (String.macrofy ("PACKAGE_" ^ name))
649 (fun ~glob -> Version.t (String.chomp
650 (Shell.string ~glob "ocamlfind query -format '%%v' %s" name)))
662 | "false" -> t := false
663 | "true" -> t := true
664 | _ -> assert false )
676 | Some false -> "false"
677 | Some true -> "true"
681 | "false" -> Some false
682 | "true" -> Some true
685 let string = String.t
689 ( ["auto"; "false"; "true"]
690 , ((:=) t <| String.t') )
697 = String.concat (String.make 1 Path.char)
699 = String.Split.char ((=) Path.char)
721 ( ["auto"; "dynamic"; "static"]
723 | "auto" -> t := `Auto
724 | "static" -> t := `Static
725 | "dynamic" -> t := `Dynamic
731 | `Static -> "static"
732 | `Dynamic -> "dynamic"
736 let mode : Mode.t ref = ref `Auto
741 = fun ~glob:{Glob.make} ->
742 match !Param.mode with
743 | `Auto -> make.Out.format "export LINKING_MODE := \n"
744 | `Static -> make.Out.format "export LINKING_MODE := static\n"
745 | `Dynamic -> make.Out.format "export LINKING_MODE := dynamic\n"
758 let bool : t ref = ref false
763 = fun ~glob:{Glob.make} ->
764 match !Param.bool with
765 | true -> make.Out.format "export DEBUG := true\n";
766 | false -> make.Out.format "export DEBUG := \n";
784 | `Cygwin -> "Cygwin"
789 | "Cygwin" -> `Cygwin
792 let string = String.t
798 ( ["Unix"; "Win32"; "Cygwin"]
799 , ((:=) t <| String.t') )
804 let type_ : Type.t ref = ref (Type.String.t' Sys.os_type)
809 = fun ~glob:{Glob.camlpp} ->
810 let type_ = Type.string !Param.type_ in
811 camlpp.Out.format "DEFINE OS_TYPE = \"%s\"\n" type_;
812 camlpp.Out.format "DEFINE %s\n" (String.uidentify type_)
818 [ "--debug" , Arg.unit Debug.Param.bool , Printf.sprintf " activate debug (DEFAULT: %s)" (Debug.string !Debug.Param.bool)
819 ; "--link-mode" , Link.Mode.Arg.t Link.Param.mode , Printf.sprintf " link mode (DEFAULT: %s)" (Link.Mode.string !Link.Param.mode)
820 ; "--os-type" , OS.Type.Arg.t OS.Param.type_ , Printf.sprintf " type of the target OS (DEFAULT: %s)" (OS.Type.string !OS.Param.type_)
821 ; "--ocamlc" , Arg.Set_string Compile.Param.ocamlc , Printf.sprintf "<command> ocamlc command (DEFAULT: %s)" !Compile.Param.ocamlc
822 ; "--ext-obj" , Arg.Set_string Compile.Param.ext_obj , Printf.sprintf "<ext> C object files extension (DEFAULT: %s)" !Compile.Param.ext_obj
823 ; "--ccomp-type", Arg.Set_string Compile.Param.ccomp_type, Printf.sprintf "<name> C compiler type (DEFAULT: %s)" !Compile.Param.ccomp_type
824 ; "--c" , Arg.Set_string Glob.Param.c , Printf.sprintf "<file> C output (DEFAULT: %s)" !Glob.Param.c
825 ; "--caml" , Arg.Set_string Glob.Param.caml , Printf.sprintf "<file> OCaml output (DEFAULT: %s)" !Glob.Param.caml
826 ; "--camlpp" , Arg.Set_string Glob.Param.camlpp , Printf.sprintf "<file> OCaml Pa_macro output (DEFAULT: %s)" !Glob.Param.camlpp
827 ; "--make" , Arg.Set_string Glob.Param.make , Printf.sprintf "<file> Makefile output (DEFAULT: %s)" !Glob.Param.make
828 ; "--log" , Arg.Set_string Glob.Param.log , Printf.sprintf "<file> shell log output (DEFAULT: %s)" !Glob.Param.log
832 = fun ?(env="") ~argv fct ->
838 "check prerequisites and generate %s.* files\n\
840 \ C_INCLUDE_PATH colon-separated paths to search C headers\n\
841 \ LIBRARY_PATH colon-separated paths to search libraries\n\
842 \ CFLAGS_<name> compile-time flags for <name>\n\
843 \ LIBS_<name> link-time flags for <name>\n\
845 OPTIONS" Glob.Param.self env);
847 (fun ({Glob.make} as glob) ->