diff options
Diffstat (limited to 'ocamlbuild/ocaml_specific.ml')
-rw-r--r-- | ocamlbuild/ocaml_specific.ml | 373 |
1 files changed, 373 insertions, 0 deletions
diff --git a/ocamlbuild/ocaml_specific.ml b/ocamlbuild/ocaml_specific.ml new file mode 100644 index 000000000..79532f8c8 --- /dev/null +++ b/ocamlbuild/ocaml_specific.ml @@ -0,0 +1,373 @@ +(***********************************************************************) +(* ocamlbuild *) +(* *) +(* Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *) +(* *) +(* Copyright 2007 Institut National de Recherche en Informatique et *) +(* en Automatique. All rights reserved. This file is distributed *) +(* under the terms of the Q Public License version 1.0. *) +(* *) +(***********************************************************************) + +(* $Id$ *) +(* Original author: Nicolas Pouillard *) +open My_std +open Format +open Log +open Pathname.Operators +open Tags.Operators +open Rule +open Tools +open Rule.Common_commands +open Outcome +open Command;; + +open Ocaml_utils + +module C_tools = struct + let link_C_library clib a libname env build = + let clib = env clib and a = env a and libname = env libname in + let objs = string_list_of_file clib in + let include_dirs = Pathname.include_dirs_of (Pathname.dirname a) in + let obj_of_o x = + if Filename.check_suffix x ".o" && !Options.ext_obj <> "o" then + Pathname.update_extension !Options.ext_obj x + else x in + let resluts = build (List.map (fun o -> List.map (fun dir -> dir / obj_of_o o) include_dirs) objs) in + let objs = List.map begin function + | Good o -> o + | Bad exn -> raise exn + end resluts in + Cmd(S[!Options.ocamlmklib; A"-o"; Px libname; T(tags_of_pathname a++"c"++"ocamlmklib"); atomize objs]);; +end + +open Flags +open Command +open Rule + +let nop _env _build = () + +let ocaml_lib ?(extern=false) ?(byte=true) ?(native=true) ?dir libpath = + let add_dir x = + match dir with + | Some dir -> S[A"-I"; P dir; x] + | None -> x + and lib = Pathname.basename libpath in + Hashtbl.replace info_libraries lib (libpath, extern); + if byte then flag ["ocaml"; "use_"^lib; "link"; "byte"] (add_dir (A (libpath^".cma"))); + if native then flag ["ocaml"; "use_"^lib; "link"; "native"] (add_dir (A (libpath^".cmxa")));; + +let init () = let module M = struct + +let ext_lib = !Options.ext_lib;; +let ext_obj = !Options.ext_obj;; +let ext_dll = !Options.ext_dll;; +let x_o = "%"-.-ext_obj;; +let x_a = "%"-.-ext_lib;; +let x_dll = "%"-.-ext_dll;; +let x_p_o = "%.p"-.-ext_obj;; +let x_p_a = "%.p"-.-ext_lib;; + +rule "target files" + ~dep:"%.itarget" + ~prod:"%.otarget" + begin fun env build -> + let itarget = env "%.itarget" and otarget = env "%.otarget" in + let dir = Pathname.dirname itarget in + List.iter ignore_good + (build (List.map (fun x -> [dir/x]) (string_list_of_file itarget))); + touch otarget + end;; + +rule "ocaml: mli -> cmi" + ~tags:["ocaml"] + ~prod:"%.cmi" + ~deps:["%.mli"; "%.mli.depends"] + (Ocaml_compiler.byte_compile_ocaml_interf "%.mli" "%.cmi");; + +rule "ocaml: mlpack & d.cmo* -> d.cmo & cmi" + ~tags:["ocaml"; "debug"; "byte"] + ~prods:["%.d.cmo"] + ~deps:["%.mlpack"; "%.cmi"] + (Ocaml_compiler.byte_debug_pack_mlpack "%.mlpack" "%.d.cmo");; + +rule "ocaml: mlpack & cmo* -> cmo & cmi" + ~tags:["ocaml"; "byte"] + ~prods:["%.cmo"; "%.cmi"] + ~dep:"%.mlpack" + (Ocaml_compiler.byte_pack_mlpack "%.mlpack" "%.cmo");; + +rule "ocaml: ml & cmi -> d.cmo" + ~tags:["ocaml"; "byte"] + ~prod:"%.d.cmo" + ~deps:["%.mli"(* This one is inserted to force this rule to be skiped when + a .ml is provided without a .mli *); "%.ml"; "%.ml.depends"; "%.cmi"] + (Ocaml_compiler.byte_compile_ocaml_implem ~tag:"debug" "%.ml" "%.d.cmo");; + +rule "ocaml: ml & cmi -> cmo" + ~tags:["ocaml"; "byte"] + ~prod:"%.cmo" + ~deps:["%.mli"(* This one is inserted to force this rule to be skiped when + a .ml is provided without a .mli *); "%.ml"; "%.ml.depends"; "%.cmi"] + (Ocaml_compiler.byte_compile_ocaml_implem "%.ml" "%.cmo");; + +rule "ocaml: mlpack & cmi & p.cmx* & p.o* -> p.cmx & p.o" + ~tags:["ocaml"; "profile"; "native"] + ~prods:["%.p.cmx"; x_p_o(* no cmi here you must make the byte version to have it *)] + ~deps:["%.mlpack"; "%.cmi"] + (Ocaml_compiler.native_profile_pack_mlpack "%.mlpack" "%.p.cmx");; + +rule "ocaml: mlpack & cmi & cmx* & o* -> cmx & o" + ~tags:["ocaml"; "native"] + ~prods:["%.cmx"; x_o(* no cmi here you must make the byte version to have it *)] + ~deps:["%.mlpack"; "%.cmi"] + (Ocaml_compiler.native_pack_mlpack "%.mlpack" "%.cmx");; + +rule "ocaml: ml & cmi -> p.cmx & p.o" + ~tags:["ocaml"; "native"; "profile"] + ~prods:["%.p.cmx"; x_p_o] + ~deps:["%.ml"; "%.ml.depends"; "%.cmi"] + (Ocaml_compiler.native_compile_ocaml_implem ~tag:"profile" ~cmx_ext:"p.cmx" "%.ml");; + +rule "ocaml: ml & cmi -> cmx & o" + ~tags:["ocaml"; "native"] + ~prods:["%.cmx"; x_o] + ~deps:["%.ml"; "%.ml.depends"; "%.cmi"] + (Ocaml_compiler.native_compile_ocaml_implem "%.ml");; + +rule "ocaml: ml -> d.cmo & cmi" + ~tags:["ocaml"; "debug"] + ~prods:["%.d.cmo"] + ~deps:["%.ml"; "%.ml.depends"; "%.cmi"] + (Ocaml_compiler.byte_compile_ocaml_implem ~tag:"debug" "%.ml" "%.d.cmo");; + +rule "ocaml: ml -> cmo & cmi" + ~tags:["ocaml"] + ~prods:["%.cmo"; "%.cmi"] + ~deps:["%.ml"; "%.ml.depends"] + (Ocaml_compiler.byte_compile_ocaml_implem "%.ml" "%.cmo");; + +rule "ocaml: d.cmo* -> d.byte" + ~tags:["ocaml"; "byte"; "debug"; "program"] + ~prod:"%.d.byte" + ~dep:"%.d.cmo" + (Ocaml_compiler.byte_debug_link "%.d.cmo" "%.d.byte");; + +rule "ocaml: cmo* -> byte" + ~tags:["ocaml"; "byte"; "program"] + ~prod:"%.byte" + ~dep:"%.cmo" + (Ocaml_compiler.byte_link "%.cmo" "%.byte");; + +rule "ocaml: p.cmx* & p.o* -> p.native" + ~tags:["ocaml"; "native"; "profile"; "program"] + ~prod:"%.p.native" + ~deps:["%.p.cmx"; x_p_o] + (Ocaml_compiler.native_profile_link "%.p.cmx" "%.p.native");; + +rule "ocaml: cmx* & o* -> native" + ~tags:["ocaml"; "native"; "program"] + ~prod:"%.native" + ~deps:["%.cmx"; x_o] + (Ocaml_compiler.native_link "%.cmx" "%.native");; + +rule "ocaml: mllib & d.cmo* -> d.cma" + ~tags:["ocaml"; "byte"; "debug"; "library"] + ~prod:"%.d.cma" + ~dep:"%.mllib" + (Ocaml_compiler.byte_debug_library_link_mllib "%.mllib" "%.d.cma");; + +rule "ocaml: mllib & cmo* -> cma" + ~tags:["ocaml"; "byte"; "library"] + ~prod:"%.cma" + ~dep:"%.mllib" + (Ocaml_compiler.byte_library_link_mllib "%.mllib" "%.cma");; + +rule "ocaml: d.cmo* -> d.cma" + ~tags:["ocaml"; "byte"; "debug"; "library"] + ~prod:"%.d.cma" + ~dep:"%.d.cmo" + (Ocaml_compiler.byte_debug_library_link "%.d.cmo" "%.d.cma");; + +rule "ocaml: cmo* -> cma" + ~tags:["ocaml"; "byte"; "library"] + ~prod:"%.cma" + ~dep:"%.cmo" + (Ocaml_compiler.byte_library_link "%.cmo" "%.cma");; + +rule "ocaml C stubs (short): clib & (o|obj)* -> (a|lib) & (so|dll)" + ~prods:["lib%(libname)"-.-ext_lib; "dll%(libname)"-.-ext_dll] + ~dep:"lib%(libname).clib" + (C_tools.link_C_library "lib%(libname).clib" ("lib%(libname)"-.-ext_lib) "%(libname)");; + +rule "ocaml C stubs: clib & (o|obj)* -> (a|lib) & (so|dll)" + ~prods:["%(path)/lib%(libname)"-.-ext_lib; "%(path)/dll%(libname)"-.-ext_dll] + ~dep:"%(path)/lib%(libname).clib" + (C_tools.link_C_library "%(path)/lib%(libname).clib" ("%(path)/lib%(libname)"-.-ext_lib) "%(path)/%(libname)");; + +rule "ocaml: mllib & p.cmx* & p.o* -> p.cmxa & p.a" + ~tags:["ocaml"; "native"; "profile"; "library"] + ~prods:["%.p.cmxa"; x_p_a] + ~dep:"%.mllib" + (Ocaml_compiler.native_profile_library_link_mllib "%.mllib" "%.p.cmxa");; + +rule "ocaml: mllib & cmx* & o* -> cmxa & a" + ~tags:["ocaml"; "native"; "library"] + ~prods:["%.cmxa"; x_a] + ~dep:"%.mllib" + (Ocaml_compiler.native_library_link_mllib "%.mllib" "%.cmxa");; + +rule "ocaml: p.cmx* & p.o* -> p.cmxa & p.a" + ~tags:["ocaml"; "native"; "profile"; "library"] + ~prods:["%.p.cmxa"; x_p_a] + ~deps:["%.p.cmx"; x_p_o] + (Ocaml_compiler.native_profile_library_link "%.p.cmx" "%.p.cmxa");; + +rule "ocaml: cmx* & o* -> cmxa & a" + ~tags:["ocaml"; "native"; "library"] + ~prods:["%.cmxa"; x_a] + ~deps:["%.cmx"; x_o] + (Ocaml_compiler.native_library_link "%.cmx" "%.cmxa");; + +Ocamldep.depends "ocaml dependencies ml" + ~prod:"%.ml.depends" + ~dep:"%.ml" ();; + +Ocamldep.depends "ocaml dependencies mli" + ~prod:"%.mli.depends" + ~dep:"%.mli" ();; + +rule "ocamllex" + ~tags:["ocaml"] (* FIXME "lexer" *) + ~prod:"%.ml" + ~dep:"%.mll" + (Ocaml_tools.ocamllex "%.mll");; + +rule "ocaml: mli -> odoc" + ~tags:["ocaml"; "doc"] + ~prod:"%.odoc" + ~deps:["%.mli"; "%.mli.depends"] + (Ocaml_tools.document_ocaml_interf "%.mli" "%.odoc");; + +rule "ocamldoc: document ocaml project *odoc -> docdir" + ~prod:"%.docdir/index.html" + ~dep:"%.odocl" + (Ocaml_tools.document_ocaml_project "%.odocl" "%.docdir");; + +(* To use menhir give the -use-menhir option at command line, + Or put true: use_menhir in your tag file. *) +if !Options.use_menhir || Configuration.has_tag "use_menhir" then begin + rule "ocaml: menhir" + ~prods:["%.ml"; "%.mli"] + ~deps:["%.mly"; "%.mly.depends"] + (Ocaml_tools.menhir "%.mly"); + + Ocamldep.depends "ocaml: menhir dependencies" + ~prod:"%.mly.depends" + ~dep:"%.mly" + ~ocamldep_command:Ocamldep.menhir_ocamldep_command (); +end else + rule "ocamlyacc" + ~tags:["ocaml"] (* FIXME "parser" *) + ~prods:["%.ml"; "%.mli"] + ~dep:"%.mly" + (Ocaml_tools.ocamlyacc "%.mly");; + +rule "ocaml C stubs: c -> o" + ~prod:x_o + ~dep:"%.c" + begin fun env _build -> + let c = env "%.c" in + let o = env x_o in + let cc = Cmd(S[!Options.ocamlc; T(tags_of_pathname c++"c"++"compile"); A"-c"; Px c]) in + if Pathname.dirname o = Pathname.current_dir_name then cc + else Seq[cc; mv (Pathname.basename o) o] + end;; + +rule "ocaml: ml & ml.depends & *cmi -> .inferred.mli" + ~prod:"%.inferred.mli" + ~deps:["%.ml"; "%.ml.depends"] + (Ocaml_tools.infer_interface "%.ml" "%.inferred.mli");; + +flag ["ocaml"; "pp"] begin + S (List.fold_right (fun x acc -> Sh x :: acc) !Options.ocaml_ppflags []) +end;; + +flag ["ocaml"; "compile"] begin + atomize !Options.ocaml_cflags +end;; + +flag ["ocaml"; "link"] begin + atomize !Options.ocaml_lflags +end;; + +flag ["ocaml"; "ocamlyacc"] (atomize !Options.ocaml_yaccflags);; + +flag ["ocaml"; "ocamllex"] (atomize !Options.ocaml_lexflags);; + +flag ["ocaml"; "byte"; "link"] begin + S (List.map (fun x -> A (x^".cma")) !Options.ocaml_libs) +end;; + +flag ["ocaml"; "native"; "link"] begin + S (List.map (fun x -> A (x^".cmxa")) !Options.ocaml_libs) +end;; + +let camlp4_flags camlp4s = + List.iter begin fun camlp4 -> + flag ["ocaml"; "pp"; camlp4] (A camlp4) + end camlp4s;; + +camlp4_flags ["camlp4o"; "camlp4r"; "camlp4of"; "camlp4rf"; "camlp4orf"];; + +ocaml_lib ~extern:true ~native:false "dynlink";; +ocaml_lib ~extern:true "unix";; +ocaml_lib ~extern:true "str";; +ocaml_lib ~extern:true "bigarray";; +ocaml_lib ~extern:true "nums";; +ocaml_lib ~extern:true "dbm";; +ocaml_lib ~extern:true "graphics";; +ocaml_lib ~extern:true "labltk";; +ocaml_lib ~extern:true ~dir:"+camlp4" "camlp4";; + +flag ["ocaml"; "debug"; "compile"; "byte"] (A "-g");; +flag ["ocaml"; "debug"; "link"; "byte"] (A "-g");; +flag ["ocaml"; "debug"; "pack"; "byte"] (A "-g");; +flag ["ocaml"; "dtypes"; "compile"] (A "-dtypes");; +flag ["ocaml"; "rectypes"; "compile"] (A "-rectypes");; +flag ["ocaml"; "linkall"; "link"] (A "-linkall");; +flag ["ocaml"; "link"; "profile"; "native"] (A "-p");; +flag ["ocaml"; "link"; "program"; "custom"; "byte"] (A "-custom");; +flag ["ocaml"; "compile"; "profile"; "native"] (A "-p");; +flag ["ocaml"; "compile"; "thread"] (A "-thread");; +flag ["ocaml"; "link"; "thread"] (S[A "threads.cmxa"; A "-thread"]);; +flag ["ocaml"; "compile"; "nopervasives"] (A"-nopervasives");; +flag ["ocaml"; "compile"; "nolabels"] (A"-nolabels");; + +(*flag ["ocaml"; "ocamlyacc"; "quiet"] (A"-q");;*) +flag ["ocaml"; "ocamllex"; "quiet"] (A"-q");; + +let ocaml_warn_flag c = + flag ["ocaml"; "compile"; sprintf "warn_%c" (Char.uppercase c)] + (S[A"-w"; A (sprintf "%c" (Char.uppercase c))]); + flag ["ocaml"; "compile"; sprintf "warn_error_%c" (Char.uppercase c)] + (S[A"-warn-error"; A (sprintf "%c" (Char.uppercase c))]); + flag ["ocaml"; "compile"; sprintf "warn_%c" (Char.lowercase c)] + (S[A"-w"; A (sprintf "%c" (Char.lowercase c))]); + flag ["ocaml"; "compile"; sprintf "warn_error_%c" (Char.lowercase c)] + (S[A"-warn-error"; A (sprintf "%c" (Char.lowercase c))]);; + +List.iter ocaml_warn_flag ['A'; 'C'; 'D'; 'E'; 'F'; 'L'; 'M'; 'P'; 'S'; 'U'; 'V'; 'Y'; 'Z'; 'X'];; + +(** Ocamlbuild plugin for it's own building *) +let install_lib = lazy (try Sys.getenv "INSTALL_LIB" with Not_found -> !*stdlib_dir/"ocamlbuild" (* not My_std.getenv since it's lazy*)) in +file_rule "ocamlbuild_where.ml" + ~prod:"%ocamlbuild_where.ml" + ~cache:(fun _ -> !*install_lib) + begin fun _ oc -> + Printf.fprintf oc "let where = ref %S;;\n" !*install_lib + end;; +ocaml_lib "ocamlbuildlib";; +ocaml_lib "ocamlbuildlightlib";; + +end in () |