summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--camlp4/Makefile4
-rw-r--r--camlp4/Makefile.ml28
-rw-r--r--camlp4/build/YaM.ml119
-rw-r--r--camlp4/build/YaM.mli2
-rw-r--r--camlp4/build/build.ml14
5 files changed, 98 insertions, 69 deletions
diff --git a/camlp4/Makefile b/camlp4/Makefile
index e6600e055..b96cce774 100644
--- a/camlp4/Makefile
+++ b/camlp4/Makefile
@@ -16,8 +16,8 @@
# Do not forget to call make genclean to update Makefile.clean before a
# release.
-OCAMLRUN=CAML_LD_LIBRARY_PATH=../otherlibs/unix ../boot/ocamlrun
-OCAML=$(OCAMLRUN) ../ocaml -I ../stdlib -I ../otherlibs/unix
+OCAMLRUN=../boot/ocamlrun -I ../otherlibs/unix -I ../otherlibs/win32unix
+OCAML=$(OCAMLRUN) ../ocaml -I ../stdlib -I ../otherlibs/unix -I ../otherlibs/win32unix
YAM=$(OCAMLRUN) ./yam
YAM_OPTIONS=-verbosity '$(VERBOSE)'
diff --git a/camlp4/Makefile.ml b/camlp4/Makefile.ml
index e9fe70ec1..35e6b646e 100644
--- a/camlp4/Makefile.ml
+++ b/camlp4/Makefile.ml
@@ -27,9 +27,19 @@ let libdir_camlp4 = (getenv "LIBDIR" Camlp4_config.libdir) ^ "/camlp4/."
let bindir = (getenv "BINDIR" Camlp4_config.bindir) ^ "/."
-let ocamlrun = "OCAMLRUNPARAM=l=1M ../boot/ocamlrun"
-
-let ocaml = ocamlrun ^ " ../ocaml -I ../stdlib -I ../otherlibs/unix "
+(**
+let unixlib =
+ match Sys.os_type with
+ | "Win32" -> "../otherlibs/win32unix"
+ | _ -> "../otherlibs/unix"
+**)
+let ocamlrun = "../boot/ocamlrun" (* " -I " ^ unixlib *)
+let ocamlrun_os =
+ Filename.concat Filename.parent_dir_name
+ (Filename.concat "boot" "ocamlrun")
+(* ^ " -I " ^ unixlib *)
+
+let ocaml = ocamlrun ^ " ../ocaml -I ../stdlib" (* "-I " ^ unixlib *)
let debug_mode =
(* true *)
@@ -37,7 +47,7 @@ let debug_mode =
let camlp4_modules =
[
- ocamlrun;
+ ocamlrun_os;
"./boot/camlp4boot";
]
let camlp4_modules =
@@ -94,7 +104,10 @@ and typing = "../typing"
and toplevel = "../toplevel"
and utils = "../utils"
and dynlink = "../otherlibs/dynlink"
-and unix = "../otherlibs/unix"
+and unix =
+ match Sys.os_type with
+ | "Win32" -> "../otherlibs/win32unix"
+ | _ -> "../otherlibs/unix"
and build = "build"
let ocaml_Module_with_meta =
@@ -386,10 +399,7 @@ let print_packed_sources ppf ?(skip = fun _ -> false) package_dir =
let run l =
let cmd = String.concat " " l in
let () = Format.printf "%s@." cmd in
- let st =
- Sys.command cmd
- (* 0 *)
- in
+ let st = YaM.call cmd in
if st <> 0 then failwith ("Exit: " ^ string_of_int st)
let mkdir l = run ("mkdir" :: "-p" :: l)
diff --git a/camlp4/build/YaM.ml b/camlp4/build/YaM.ml
index cf1ea04cb..00b2937b8 100644
--- a/camlp4/build/YaM.ml
+++ b/camlp4/build/YaM.ml
@@ -1,22 +1,14 @@
-(*
- *
- * Copyright (C) 2003-2004 Damien Pous
- *
- * YaM is free software; you can redistribute it and/or modify
- * it under the terms of the GNU General Public License as published by
- * the Free Software Foundation; either version 2 of the License, or
- * (at your option) any later version.
- *
- * YaM is distributed in the hope that it will be useful,
- * but WITHOUT ANY WARRANTY; without even the implied warranty of
- * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- * GNU General Public License for more details.
- *
- * You should have received a copy of the GNU General Public License
- * along with YaM; if not, write to the Free Software
- * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
- *
- *)
+(* * * Copyright (C) 2003-2004 Damien Pous * * YaM is free software;
+you can redistribute it and/or modify * it under the terms of the GNU
+General Public License as published by * the Free Software Foundation;
+either version 2 of the License, or * (at your option) any later
+version. * * YaM is distributed in the hope that it will be useful, *
+but WITHOUT ANY WARRANTY; without even the implied warranty of *
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU
+General Public License for more details. * * You should have received
+a copy of the GNU General Public License * along with YaM; if not,
+write to the Free Software * Foundation, Inc., 59 Temple Place, Suite
+330, Boston, MA 02111-1307 USA * *)
open Printf
@@ -179,10 +171,21 @@ let silent_remove f = try Sys.remove f with Sys_error _ -> ()
let touch_file f = if not (Sys.file_exists f) then close_out (open_out f)
exception CmdError of string
-let call = Sys.command
+
+let makecommand =
+ match Sys.os_type with
+ | "Win32" -> (fun cmd -> "bash -c " ^ Filename.quote cmd)
+ | _ -> (fun cmd -> cmd)
+
+let call cmd = Sys.command (makecommand cmd)
let ecall cmd = if (call cmd) <> 0 then raise (CmdError cmd)
let exitf ?(err=1) x = kprintf (fun msg -> eprintf "%s" msg; exit err) x
+let fileconcat dirname filename =
+ let l = String.length dirname in
+ if l = 0 || dirname.[l-1] = '/'
+ then dirname ^ filename
+ else dirname ^ "/" ^ filename
let mk_ext e = (fun n -> n^e), (fun n -> Filename.check_suffix n e)
let ml , is_ml = mk_ext ".ml"
@@ -211,10 +214,28 @@ let rec fold_units f a = function
| u::q -> fold_units f (f u (fold_units f a u.sub_units)) q
let get_line c =
- let s = input_line c in
- s, String.length s
-
-
+ let rec get accu =
+ let s = input_line c in
+ let l = String.length s in
+ if l > 0 && s.[l-1] = '\\'
+ then get (String.sub s 0 (l-1) :: accu)
+ else if l > 1 && s.[l-1] = '\r' && s.[l-2] = '\\'
+ then get (String.sub s 0 (l-2) :: accu)
+ else String.concat "" (List.rev (s :: accu))
+ in get []
+
+let split_string pred s =
+ let rec split1 i accu =
+ if i >= String.length s
+ then List.rev accu
+ else if pred s.[i] then split1 (i+1) accu
+ else split2 i (i+1) accu
+ and split2 i j accu =
+ if j >= String.length s
+ then List.rev (String.sub s i (j-i) :: accu)
+ else if pred s.[j] then split1 (j+1) (String.sub s i (j-i) :: accu)
+ else split2 i (j+1) accu
+ in split1 0 []
(* ---- Outils OCaml (c,dep,opt...) ---- *)
@@ -222,31 +243,19 @@ let get_line c =
(* parsing de la sortie d'ocamldep *)
let tokenize ?(skip=false) c =
try
- if skip then (
- (* ignorage du premier bloc (cmo/cmx) *)
- let last c = let s = input_line c in s.[String.length s - 1] in
- try while last c = '\\' do () done
- with End_of_file -> ()
- );
- let s,ls = get_line c in
- let i = String.index s ':' in
- let rec aux i acc ((s,ls) as sls) =
- if s.[i]='\\' then aux 4 acc (get_line c)
- else
- let j = String.index_from s i ' ' in
- if j+1 = ls then String.sub s i (j-i) :: acc
- else let k,sls' = if s.[j+1]='\\' then 4, get_line c else j+1, sls in
- aux k (String.sub s i (j-i) :: acc) sls'
- in
- aux (i+2) [] (s,ls)
+ if skip then ignore (get_line c);
+ match split_string (function ' ' | ':' -> true | _ -> false)
+ (get_line c) with
+ | [] -> []
+ | _ :: deps -> deps
with End_of_file -> []
let ocamldep ~native ~depc ~sf =
let nat = if native then "-native " else "" in
- let cmd = depc^^nat^^sf in
+ let cmd = depc^^"-slash"^^nat^^sf in
if !print_deps then printf "%s\n%!" cmd
else printf "DEPENDENCIES: %s\n%!" sf;
- let c_in = Unix.open_process_in cmd in
+ let c_in = Unix.open_process_in (makecommand cmd) in
let deps = tokenize ~skip:(native && is_ml sf) c_in in
let deps' =
if native then deps
@@ -276,7 +285,7 @@ let ocaml_options ?(o= !options) ?(flags="") ?(byte_flags="") ?(opt_flags="") ?p
let opt_flags' = (print_inc !(o.ocaml_Includes))^^(print_inc includes)^^(print_p4 (oget !(o.ocaml_P4_opt) pp)) in
let opt_flags' = !(o.ocaml_Flags)^^flags^^(print_inc !(o.ocaml_ExtIncludes))^^(print_inc ext_includes)^^opt_flags' in
let optc = !(o.ocamlopt)^^(for_pack o)^^opt_flags'^^opt_flags ^^ !(o.ocaml_OptFlags) in
- (Filename.concat !dir n), depc, bytec, optc
+ (fileconcat !dir n), depc, bytec, optc
@@ -383,8 +392,8 @@ let ocaml_Interface ?o ?flags ?byte_flags ?opt_flags ?pp ?includes ?ext_includes
(* objet C *)
let c_Module ?(o= !options) ?(flags="") ?(source_deps=[]) n =
- let n = Filename.concat !dir n in
- let sources = List.map (Filename.concat !dir) source_deps in
+ let n = fileconcat !dir n in
+ let sources = List.map (fileconcat !dir) source_deps in
let c_n, o_n = cc n, oo n in
let cc = !(o.ocamlc)^" -c"^^flags^^c_n in
let sources = c_n::sources in
@@ -399,7 +408,7 @@ let c_Module ?(o= !options) ?(flags="") ?(source_deps=[]) n =
(* lexer ocaml *)
let ocaml_Lexer ?(o= !options) ?flags ?byte_flags ?opt_flags ?(lex_flags="") ?pp ?includes ?ext_includes n =
- let n' = Filename.concat !dir n in
+ let n' = fileconcat !dir n in
let mll_n, ml_n = mll n', ml n' in
let ocamllex = !(o.ocamllex)^^lex_flags^^mll_n in
generic_unit
@@ -414,7 +423,7 @@ let ocaml_Lexer ?(o= !options) ?flags ?byte_flags ?opt_flags ?(lex_flags="") ?pp
(* parser ocaml *)
let ocaml_Parser ?(o= !options) ?flags ?byte_flags ?opt_flags ?(yacc_flags="") ?pp ?includes ?ext_includes n =
- let n' = Filename.concat !dir n in
+ let n' = fileconcat !dir n in
let mly_n, ml_n, mli_n = mly n', ml n', mli n' in
let ocamlyacc = !(o.ocamlyacc)^^yacc_flags^^mly_n in
let gen = [ml_n; mli_n] in
@@ -430,7 +439,7 @@ let ocaml_Parser ?(o= !options) ?flags ?byte_flags ?opt_flags ?(yacc_flags="") ?
(* interface glade à compiler en ocaml *)
let ocaml_Glade ?(o= !options) ?flags ?byte_flags ?opt_flags ?(glade_flags="") ?pp ?includes ?ext_includes n =
- let n' = Filename.concat !dir n in
+ let n' = fileconcat !dir n in
let glade_n, ml_n = glade n', ml n' in
let ocamlglade = !(o.ocamlglade)^^glade_flags^^glade_n^" > "^ml_n in
generic_unit
@@ -445,7 +454,7 @@ let ocaml_Glade ?(o= !options) ?flags ?byte_flags ?opt_flags ?(glade_flags="") ?
(* paquet de modules ocaml *)
let ocaml_Package ?(o= !options) n sub_units =
- let n = Filename.concat !dir n in
+ let n = fileconcat !dir n in
let ml_n, cmo_n, cmi_n, cmx_n, o_n = ml n, cmo n, cmi n, cmx n, oo n in
let otmap2 f = List.fold_right
(function { objects=None; targets=[x] }
@@ -481,9 +490,9 @@ let add_for_pack o n =
(* paquet de modules regroupés dans un sous répertoire *)
let ocaml_PackageDir ?o n l =
- let n' = Filename.concat !dir n in
+ let n' = fileconcat !dir n in
let dir' = !dir in
- dir := Filename.concat n' "";
+ dir := fileconcat n' "";
let l' = new_scope (lazy (!options.ocaml_Includes += n';
add_for_pack !options n; Lazy.force l)) in
dir := dir';
@@ -572,7 +581,7 @@ let fold_units_sources units f =
(* (\* unité utilisateur *\) *)
(* let user_unit ?trash ~command ~depends name = *)
-(* let targets = [Filename.concat !dir name] in *)
+(* let targets = [fileconcat !dir name] in *)
(* let trash = oget targets trash in *)
(* generic_unit ~targets ~trash *)
(* ~dependencies:(fun ~native _ -> depends) *)
@@ -682,7 +691,7 @@ let project ?(rebuild="ocaml build.ml") ?(deps=["Makefile.ml"]) units =
let rebuild = ref rebuild in
for i=1 to Array.length Sys.argv -1 do rebuild := !rebuild^" "^Sys.argv.(i) done;
printf "yam is out-dated, rebuilding it (%s)\n%!" !rebuild;
- exit (Sys.command !rebuild)
+ exit (call !rebuild)
) in
(* construction de la table cible -> unités *)
@@ -887,7 +896,7 @@ let rec best =
| [] -> invalid_arg "YaM.best: []"
let scall cmd =
- let cin = Unix.open_process_in cmd in
+ let cin = Unix.open_process_in (makecommand cmd) in
let str = input_line cin in str
let which x = scall ("which"^^x)
diff --git a/camlp4/build/YaM.mli b/camlp4/build/YaM.mli
index ea35c2a68..f0c68433b 100644
--- a/camlp4/build/YaM.mli
+++ b/camlp4/build/YaM.mli
@@ -304,3 +304,5 @@ val getenv: string -> string -> string
val which : string -> string
val is_file_empty : string -> bool
+
+val call : string -> int
diff --git a/camlp4/build/build.ml b/camlp4/build/build.ml
index 244991e9a..408771427 100644
--- a/camlp4/build/build.ml
+++ b/camlp4/build/build.ml
@@ -7,9 +7,17 @@
let makefile = "Makefile.ml"
(* Environment options *)
-let ocamlrun = "OCAMLRUNPARAM=l=1M CAML_LD_LIBRARY_PATH=../otherlibs/unix ../boot/ocamlrun"
-let ocamlc = ocamlrun ^ " ../ocamlc -nostdlib -I ../stdlib -I ../otherlibs/unix"
-let ocamlopt = ocamlrun ^ " ../ocamlopt -nostdlib -I ../stdlib -I ../otherlibs/unix"
+let unixlib =
+ match Sys.os_type with
+ | "Win32" -> "../otherlibs/win32unix"
+ | _ -> "../otherlibs/unix"
+
+let ocamlrun =
+ Filename.concat Filename.parent_dir_name (Filename.concat "boot" "ocamlrun")
+ ^ " -I " ^ unixlib
+
+let ocamlc = ocamlrun ^ " ../ocamlc -g -nostdlib -I ../stdlib -I " ^ unixlib
+let ocamlopt = ocamlrun ^ " ../ocamlopt -nostdlib -I ../stdlib -I " ^ unixlib
let yam = ocamlrun ^ " ./yam "
(* Compile YaM in native mode ? *)