2006-06-29 01:12:46 -07:00
|
|
|
(****************************************************************************)
|
|
|
|
(* *)
|
|
|
|
(* Objective Caml *)
|
|
|
|
(* *)
|
|
|
|
(* INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2006 Institut National de Recherche en Informatique et *)
|
|
|
|
(* en Automatique. All rights reserved. This file is distributed under *)
|
|
|
|
(* the terms of the GNU Library General Public License, with the special *)
|
|
|
|
(* exception on linking described in LICENSE at the top of the Objective *)
|
|
|
|
(* Caml source tree. *)
|
|
|
|
(* *)
|
|
|
|
(****************************************************************************)
|
|
|
|
|
|
|
|
(* Authors:
|
|
|
|
* - Nicolas Pouillard: initial version
|
|
|
|
*)
|
|
|
|
open YaM
|
|
|
|
open Format
|
|
|
|
|
|
|
|
let getenv var default =
|
|
|
|
try Sys.getenv var
|
|
|
|
with Not_found ->
|
|
|
|
default
|
|
|
|
|
|
|
|
let libdir_camlp4 = (getenv "LIBDIR" Camlp4_config.libdir) ^ "/camlp4/."
|
|
|
|
|
|
|
|
let bindir = (getenv "BINDIR" Camlp4_config.bindir) ^ "/."
|
|
|
|
|
2006-09-28 06:30:03 -07:00
|
|
|
(**
|
|
|
|
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 *)
|
2006-06-29 01:12:46 -07:00
|
|
|
|
|
|
|
let debug_mode =
|
|
|
|
(* true *)
|
|
|
|
false
|
|
|
|
|
|
|
|
let camlp4_modules =
|
|
|
|
[
|
2006-09-28 06:30:03 -07:00
|
|
|
ocamlrun_os;
|
2006-06-29 01:12:46 -07:00
|
|
|
"./boot/camlp4boot";
|
|
|
|
]
|
|
|
|
let camlp4_modules =
|
|
|
|
if debug_mode then "env STATIC_CAMLP4_DEBUG=\\*" :: camlp4_modules
|
|
|
|
else camlp4_modules
|
|
|
|
|
2006-07-08 09:52:30 -07:00
|
|
|
let debug_opt x = if debug_mode && Sys.file_exists x then [x] else []
|
|
|
|
let filter_opt x = if Sys.file_exists x then [x] else []
|
|
|
|
|
2006-06-29 01:12:46 -07:00
|
|
|
let camlp4boot = "'" ^ String.concat " " camlp4_modules ^ "'"
|
|
|
|
let camlp4boot_may_debug mods =
|
2006-07-08 09:52:30 -07:00
|
|
|
let camlp4_modules = camlp4_modules @
|
|
|
|
debug_opt "./boot/ExceptionTracer.cmo" @
|
|
|
|
filter_opt "./boot/Profiler.cmo" @ mods
|
2006-06-29 01:12:46 -07:00
|
|
|
in "'" ^ String.concat " " camlp4_modules ^ "'"
|
|
|
|
|
2006-07-18 08:05:10 -07:00
|
|
|
let ocamlc =
|
|
|
|
best ["../ocamlc.opt", "../ocamlc.opt";
|
2006-07-22 04:18:26 -07:00
|
|
|
"../ocamlc", ocamlrun ^^ "../ocamlc";
|
|
|
|
"", "echo no byte compiler available && false"]
|
2006-07-18 08:05:10 -07:00
|
|
|
let ocamlopt =
|
|
|
|
best ["../ocamlopt.opt", "../ocamlopt.opt";
|
2006-07-22 04:18:26 -07:00
|
|
|
"../ocamlopt", ocamlrun ^^ "../ocamlopt";
|
|
|
|
"", "echo no native compiler available && false"]
|
2006-07-18 08:05:10 -07:00
|
|
|
|
2006-06-29 01:12:46 -07:00
|
|
|
let () =
|
2006-07-18 08:05:10 -07:00
|
|
|
!options.ocamlc := ocamlc ^^ " -nostdlib -I ../stdlib";
|
|
|
|
!options.ocamlopt := ocamlopt ^^ " -nostdlib -I ../stdlib";
|
2006-06-29 01:12:46 -07:00
|
|
|
!options.ocamldoc := ocamlrun ^^ "../ocamldoc/ocamldoc";
|
|
|
|
!options.ocamlyacc := ocamlrun ^^ "../boot/ocamlyacc";
|
|
|
|
!options.ocamllex := ocamlrun ^^ "../boot/ocamllex";
|
|
|
|
!options.ocamldep := ocamlrun ^^ "../tools/ocamldep";
|
|
|
|
()
|
|
|
|
|
|
|
|
let options_without_camlp4 = new_scope (lazy !options)
|
|
|
|
|
2006-09-20 08:39:30 -07:00
|
|
|
let windows = Sys.os_type = "Win32"
|
|
|
|
|
|
|
|
let may_define_unix = if windows then [] else ["-D UNIX"]
|
|
|
|
|
2006-06-29 01:12:46 -07:00
|
|
|
let () =
|
2009-10-22 08:45:54 -07:00
|
|
|
!options.ocaml_Flags ^= "-w Aler -warn-error Aler"^^
|
2010-01-20 08:26:46 -08:00
|
|
|
(if getenv "DTYPES" "" <> "" then "-annot"
|
2006-08-09 06:55:45 -07:00
|
|
|
else "");
|
2006-09-20 08:39:30 -07:00
|
|
|
!options.ocaml_P4 := camlp4boot_may_debug may_define_unix;
|
|
|
|
!options.ocaml_P4_opt := camlp4boot_may_debug ("-D OPT" :: may_define_unix);
|
2006-06-29 01:12:46 -07:00
|
|
|
()
|
|
|
|
|
|
|
|
let options_without_debug () = { (!options) with ocaml_P4 = ref camlp4boot
|
|
|
|
; ocaml_P4_opt = ref camlp4boot }
|
|
|
|
|
|
|
|
let parsing = "../parsing"
|
|
|
|
and typing = "../typing"
|
|
|
|
and toplevel = "../toplevel"
|
|
|
|
and utils = "../utils"
|
|
|
|
and dynlink = "../otherlibs/dynlink"
|
2006-09-28 06:30:03 -07:00
|
|
|
and unix =
|
|
|
|
match Sys.os_type with
|
|
|
|
| "Win32" -> "../otherlibs/win32unix"
|
|
|
|
| _ -> "../otherlibs/unix"
|
2006-06-29 01:12:46 -07:00
|
|
|
and build = "build"
|
|
|
|
|
|
|
|
let ocaml_Module_with_genmap =
|
|
|
|
generic_ocaml_Module_extension ".genmap.ml"
|
|
|
|
(fun _ i o ->
|
|
|
|
"if test ! -e"^^o^^
|
2006-10-02 05:59:01 -07:00
|
|
|
"|| ( test -e ./camlp4boot.run"^^
|
2006-07-17 07:19:59 -07:00
|
|
|
"&& test -e Camlp4Filters/GenerateMap.cmo"^^
|
|
|
|
"&& test -e Camlp4Filters/GenerateFold.cmo"^^
|
2006-10-04 09:22:54 -07:00
|
|
|
"&& test -e Camlp4Filters/MetaGenerator.cmo"^^
|
2006-10-02 05:59:01 -07:00
|
|
|
"&& test -e Camlp4Filters/RemoveTrashModule.cmo ) ;"^^
|
|
|
|
"then ( echo 'module Camlp4FiltersTrash = struct' ;"^^
|
|
|
|
"cat Camlp4/Sig/Camlp4Ast.ml ; echo 'end;' ) > Camlp4/Struct/Camlp4Ast.tmp.ml ;"^^
|
|
|
|
"( echo '(* Generated file! Do not edit by hand *)' ;"^^
|
|
|
|
"../boot/ocamlrun ./camlp4boot.run"^^
|
2006-07-17 07:19:59 -07:00
|
|
|
"./Camlp4Filters/GenerateMap.cmo"^^
|
|
|
|
"./Camlp4Filters/GenerateFold.cmo"^^
|
2006-10-04 09:22:54 -07:00
|
|
|
"./Camlp4Filters/MetaGenerator.cmo"^^
|
2006-07-17 07:19:59 -07:00
|
|
|
"./Camlp4Filters/RemoveTrashModule.cmo -printer OCamlr"^^
|
2006-10-02 05:59:01 -07:00
|
|
|
i^^" -no_comments ) >"^^o^^"; else : ; fi")
|
2006-06-29 01:12:46 -07:00
|
|
|
|
2006-09-06 08:43:03 -07:00
|
|
|
let camlp4_package_as_one_dir =
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_PackageDir "Camlp4" (lazy [
|
|
|
|
ocaml_IModule ~includes:[build] "Config";
|
2006-09-06 08:43:03 -07:00
|
|
|
ocaml_IModule ~o:(options_without_debug ()) "Debug";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_IModule "Options";
|
|
|
|
ocaml_PackageDir "Sig" (lazy [
|
|
|
|
ocaml_Interface "Id";
|
2006-09-06 08:43:03 -07:00
|
|
|
ocaml_Interface ~ext_includes:[parsing] "Loc";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_Interface "Error";
|
|
|
|
ocaml_Interface "Warning";
|
|
|
|
ocaml_Interface "Type";
|
|
|
|
ocaml_Interface "Token";
|
|
|
|
ocaml_Interface "Lexer";
|
|
|
|
ocaml_PackageDir "Grammar" (lazy [
|
|
|
|
ocaml_Interface "Action";
|
|
|
|
ocaml_Interface "Structure";
|
|
|
|
ocaml_Interface "Dynamic";
|
|
|
|
ocaml_Interface "Static"
|
|
|
|
]);
|
|
|
|
ocaml_IModule "Mapper";
|
|
|
|
ocaml_Interface "Ast";
|
|
|
|
ocaml_Module "Camlp4Ast";
|
|
|
|
ocaml_Interface "Quotation";
|
|
|
|
ocaml_Interface "Camlp4Token";
|
|
|
|
ocaml_Interface "DynLoader";
|
|
|
|
ocaml_Interface "AntiquotSyntax";
|
|
|
|
ocaml_Interface "Parser";
|
|
|
|
ocaml_Interface "Printer";
|
|
|
|
ocaml_Interface "Syntax";
|
|
|
|
ocaml_Interface "Camlp4Syntax";
|
|
|
|
ocaml_Interface "AstFilters";
|
|
|
|
ocaml_Interface "SyntaxExtension";
|
|
|
|
]);
|
|
|
|
ocaml_IModule "ErrorHandler";
|
|
|
|
ocaml_PackageDir "Struct" (lazy [
|
|
|
|
ocaml_IModule ~ext_includes:[parsing] "Loc";
|
|
|
|
ocaml_Module "Warning";
|
|
|
|
ocaml_IModule "EmptyError";
|
|
|
|
ocaml_IModule "EmptyPrinter";
|
|
|
|
ocaml_IModule "Token";
|
|
|
|
ocaml_Lexer ~includes:[utils] ~ext_includes:[parsing] ~pp:"" "Lexer";
|
|
|
|
ocaml_PackageDir "Grammar" (lazy [
|
|
|
|
ocaml_Module "Context";
|
|
|
|
ocaml_Module "Structure";
|
|
|
|
ocaml_Module "Search";
|
|
|
|
ocaml_Module "Tools";
|
2006-09-06 08:43:03 -07:00
|
|
|
ocaml_IModule "Print";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_Module "Failed";
|
|
|
|
ocaml_Module "Parser";
|
2006-06-29 14:51:42 -07:00
|
|
|
ocaml_IModule "Fold";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_Module "Insert";
|
|
|
|
ocaml_Module "Delete";
|
|
|
|
ocaml_Module "Entry";
|
|
|
|
ocaml_Module "Find";
|
|
|
|
ocaml_Module "Dynamic";
|
|
|
|
ocaml_Module "Static"
|
|
|
|
]);
|
|
|
|
ocaml_Module "Quotation";
|
|
|
|
ocaml_IModule ~ext_includes:[dynlink] "DynLoader";
|
|
|
|
ocaml_Module_with_genmap ~flags:"-w z -warn-error z" "Camlp4Ast";
|
2006-07-17 07:19:59 -07:00
|
|
|
ocaml_IModule "FreeVars";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_Module "AstFilters";
|
|
|
|
ocaml_IModule ~ext_includes:[parsing] "Camlp4Ast2OCamlAst";
|
2006-09-06 08:43:03 -07:00
|
|
|
ocaml_Module "CleanAst";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_IModule "CommentFilter";
|
|
|
|
]);
|
|
|
|
ocaml_Module "OCamlInitSyntax";
|
|
|
|
ocaml_PackageDir "Printers" (lazy [
|
2006-10-02 05:59:01 -07:00
|
|
|
ocaml_IModule "Null";
|
2006-06-29 08:01:37 -07:00
|
|
|
ocaml_IModule "DumpOCamlAst";
|
|
|
|
ocaml_IModule "DumpCamlp4Ast";
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_IModule "OCaml";
|
|
|
|
ocaml_IModule "OCamlr" ~flags:"-w v -warn-error v";
|
2006-07-17 07:19:59 -07:00
|
|
|
(* ocaml_IModule "OCamlrr"; *)
|
2006-10-02 05:59:01 -07:00
|
|
|
]);
|
|
|
|
ocaml_IModule "PreCast";
|
|
|
|
ocaml_IModule "Register"
|
2006-06-29 01:12:46 -07:00
|
|
|
])
|
|
|
|
|
|
|
|
let camlp4_parsers =
|
|
|
|
ocaml_PackageDir "Camlp4Parsers" (lazy [
|
|
|
|
ocaml_Module "OCamlr";
|
|
|
|
ocaml_Module "OCaml";
|
2006-07-17 07:19:59 -07:00
|
|
|
(* ocaml_Module "OCamlrr"; *)
|
2006-06-29 01:12:46 -07:00
|
|
|
ocaml_Module "OCamlQuotationBase";
|
|
|
|
ocaml_Module "OCamlQuotation";
|
|
|
|
ocaml_Module "OCamlRevisedQuotation";
|
|
|
|
ocaml_Module "OCamlOriginalQuotation";
|
|
|
|
ocaml_Module "OCamlRevisedParser";
|
|
|
|
ocaml_Module "OCamlParser";
|
|
|
|
ocaml_Module "Grammar";
|
|
|
|
ocaml_Module "Macro";
|
|
|
|
ocaml_Module ~o:(options_without_debug ()) "Debug";
|
|
|
|
ocaml_Module "LoadCamlp4Ast";
|
|
|
|
])
|
|
|
|
|
|
|
|
let camlp4_printers =
|
|
|
|
ocaml_PackageDir "Camlp4Printers" (lazy [
|
|
|
|
ocaml_Module "DumpOCamlAst";
|
|
|
|
ocaml_Module "DumpCamlp4Ast";
|
|
|
|
ocaml_Module "OCaml";
|
|
|
|
ocaml_Module "OCamlr";
|
2006-07-17 07:19:59 -07:00
|
|
|
(* ocaml_Module "OCamlrr"; *)
|
2006-06-29 14:51:42 -07:00
|
|
|
ocaml_Module "Null";
|
2006-09-06 08:43:03 -07:00
|
|
|
ocaml_Module ~ext_includes:[unix] "Auto";
|
2006-06-29 01:12:46 -07:00
|
|
|
])
|
|
|
|
|
|
|
|
let camlp4_filters =
|
|
|
|
ocaml_PackageDir "Camlp4Filters" (lazy [
|
|
|
|
ocaml_Module "ExceptionTracer";
|
|
|
|
ocaml_Module "Tracer";
|
|
|
|
ocaml_Module "StripLocations";
|
|
|
|
ocaml_Module "LiftCamlp4Ast";
|
|
|
|
ocaml_Module "GenerateMap";
|
2006-07-17 07:19:59 -07:00
|
|
|
ocaml_Module "GenerateFold";
|
2006-10-04 09:22:54 -07:00
|
|
|
ocaml_Module "MetaGenerator";
|
2006-07-17 07:19:59 -07:00
|
|
|
ocaml_Module "RemoveTrashModule";
|
2006-07-08 09:52:30 -07:00
|
|
|
ocaml_Module "Profiler";
|
2006-06-29 01:12:46 -07:00
|
|
|
])
|
|
|
|
|
|
|
|
let camlp4_top =
|
|
|
|
ocaml_PackageDir "Camlp4Top" (lazy [
|
2006-09-06 08:43:03 -07:00
|
|
|
ocaml_Module ~ext_includes:[toplevel; typing; parsing] "Rprint";
|
|
|
|
ocaml_Module ~ext_includes:[toplevel; parsing; utils] "Camlp4Top";
|
2006-06-29 01:12:46 -07:00
|
|
|
])
|
|
|
|
|
|
|
|
let split c s =
|
|
|
|
let rec self acc s =
|
|
|
|
try
|
|
|
|
let pos = String.rindex s c in
|
|
|
|
let x = String.sub s 0 pos
|
|
|
|
and y = String.sub s (pos + 1) (String.length s - pos - 1)
|
|
|
|
in self (y :: acc) x
|
|
|
|
with Not_found -> s :: acc
|
|
|
|
in self [] s
|
|
|
|
let chop_end c s =
|
|
|
|
let pos = String.rindex s c in
|
|
|
|
String.sub s (pos + 1) (String.length s - pos - 1)
|
|
|
|
let file ppf f =
|
|
|
|
let cin = open_in f in
|
|
|
|
let rec loop () =
|
|
|
|
pp_print_string ppf (input_line cin);
|
|
|
|
fprintf ppf "@\n";
|
|
|
|
loop ()
|
|
|
|
in try loop () with End_of_file -> ()
|
|
|
|
let ext_split f = split '.' f
|
2010-01-22 04:48:24 -08:00
|
|
|
|
|
|
|
|
2006-07-05 04:22:32 -07:00
|
|
|
let print_packed_sources ppf ?(skip = fun _ -> false) package_dir =
|
2006-06-29 01:12:46 -07:00
|
|
|
let _ =
|
2006-07-05 04:22:32 -07:00
|
|
|
fold_units_sources [package_dir] (fun name sources k (skip, inside) ->
|
2006-06-29 01:12:46 -07:00
|
|
|
eprintf "%s: [%s] (%b)@." name (String.concat "; " sources) inside;
|
|
|
|
let name = try chop_end '/' name with Not_found -> name in
|
2006-07-05 04:22:32 -07:00
|
|
|
let k () = ignore (k (skip, true)) in
|
2006-06-29 01:12:46 -07:00
|
|
|
if not inside then k () else (
|
2006-07-05 04:22:32 -07:00
|
|
|
if skip name then fprintf ppf "(**/**)@\n" else fprintf ppf "(** *)@\n";
|
2006-06-29 01:12:46 -07:00
|
|
|
fprintf ppf "@[<2>module %s " name;
|
2006-07-05 04:22:32 -07:00
|
|
|
let (mli, ml, mll, k) =
|
2006-06-29 01:12:46 -07:00
|
|
|
List.fold_right
|
2006-07-05 04:22:32 -07:00
|
|
|
(fun x (mli, ml, mll, k) ->
|
2006-06-29 01:12:46 -07:00
|
|
|
match ext_split x with
|
2006-07-05 04:22:32 -07:00
|
|
|
| [_; "mli"] -> (Some x, ml, mll, k)
|
|
|
|
| [_; "ml"] -> (mli, Some x, mll, k)
|
|
|
|
| [_; "mll"] -> (mli, ml, Some x, k)
|
|
|
|
| [x; "meta"; "ml"] -> (mli, Some (x^".ml"), mll, fun () -> ())
|
|
|
|
| [x; "genmap"; "ml"] -> (mli, Some (x^".ml"), mll, fun () -> ())
|
2006-06-29 01:12:46 -07:00
|
|
|
| [_; ext] -> failwith ("unknown extension " ^ ext)
|
|
|
|
| _ -> failwith ("bad file "^x))
|
2006-07-05 04:22:32 -07:00
|
|
|
sources (None, None, None, k) in
|
|
|
|
(match (ml, mll, mli) with
|
|
|
|
| (None, None, Some mli) -> fprintf ppf "=@ @[<2>struct@\n"
|
|
|
|
| (_, _, Some mli) -> fprintf ppf ":@,@[<2>sig@\n%a@]@\nend@\n" file mli;
|
|
|
|
fprintf ppf "=@ @[<2>struct@\n"
|
|
|
|
| _ -> fprintf ppf "=@ @[<2>struct@\n");
|
2006-06-29 01:12:46 -07:00
|
|
|
(match (ml, mll, mli) with
|
|
|
|
| (_, Some mll, _) ->
|
|
|
|
fprintf ppf "(*___CAMLP4_LEXER___ %a ___CAMLP4_LEXER___*)@\n();"
|
|
|
|
file (String.sub mll 0 (String.length mll - 1))
|
|
|
|
| (Some ml, _, _) -> k (); fprintf ppf "%a" file ml
|
|
|
|
| (None, _, Some mli) -> k (); fprintf ppf "%a" file mli
|
|
|
|
| _ -> if sources <> [] then () else k ());
|
2006-07-05 04:22:32 -07:00
|
|
|
fprintf ppf "@]@\nend;@]@\n";
|
|
|
|
if skip name then fprintf ppf "(**/**)@\n";
|
2006-06-29 01:12:46 -07:00
|
|
|
);
|
2006-07-05 04:22:32 -07:00
|
|
|
(skip, inside)
|
|
|
|
) (skip, false) in fprintf ppf "@."
|
2006-06-29 01:12:46 -07:00
|
|
|
|
|
|
|
let run l =
|
|
|
|
let cmd = String.concat " " l in
|
|
|
|
let () = Format.printf "%s@." cmd in
|
2006-09-28 06:30:03 -07:00
|
|
|
let st = YaM.call cmd in
|
2006-06-29 01:12:46 -07:00
|
|
|
if st <> 0 then failwith ("Exit: " ^ string_of_int st)
|
|
|
|
|
|
|
|
let sed re str file =
|
|
|
|
run ["sed"; "-i"; "-e"; "'s/"^re^"/"^str^"/'"; file]
|
|
|
|
|
2006-09-06 08:43:03 -07:00
|
|
|
let pack () =
|
2006-06-29 01:12:46 -07:00
|
|
|
let revised_to_ocaml f =
|
2006-07-05 04:22:32 -07:00
|
|
|
run ["./boot/camlp4boot -printer OCaml -o "^f^".ml -impl "^f^".ml4"] in
|
2006-06-29 01:12:46 -07:00
|
|
|
let ppf_of_file f = formatter_of_out_channel (open_out f) in
|
2006-07-05 04:22:32 -07:00
|
|
|
let skip_struct = function "Struct" -> true | _ -> false in
|
2006-09-06 08:43:03 -07:00
|
|
|
print_packed_sources (ppf_of_file "Camlp4.ml4")
|
|
|
|
~skip:skip_struct camlp4_package_as_one_dir;
|
|
|
|
print_packed_sources (ppf_of_file "Camlp4Parsers.ml4") camlp4_parsers;
|
|
|
|
print_packed_sources (ppf_of_file "Camlp4Printers.ml4") camlp4_printers;
|
|
|
|
print_packed_sources (ppf_of_file "Camlp4Filters.ml4") camlp4_filters;
|
|
|
|
print_packed_sources (ppf_of_file "Camlp4Top.ml4") camlp4_top;
|
|
|
|
revised_to_ocaml "Camlp4";
|
|
|
|
sed "(\\*___CAMLP4_LEXER___" "" "Camlp4.ml";
|
|
|
|
sed "___CAMLP4_LEXER___\\*)" "" "Camlp4.ml";
|
|
|
|
sed "^ *# [0-9]\\+.*$" "" "Camlp4.ml";
|
|
|
|
revised_to_ocaml "Camlp4Parsers";
|
|
|
|
revised_to_ocaml "Camlp4Printers";
|
|
|
|
revised_to_ocaml "Camlp4Filters";
|
|
|
|
revised_to_ocaml "Camlp4Top"
|
|
|
|
|
|
|
|
let just_doc () =
|
|
|
|
run ["cd doc && ../../ocamldoc/ocamldoc";
|
|
|
|
"-v -short-functors -html";
|
|
|
|
"-I ../../parsing -I ../build -I ../../utils -I ..";
|
|
|
|
"-dump ocamldoc.out";
|
|
|
|
"-t 'Camlp4 a Pre-Processor-Pretty-Printer for Objective Caml'";
|
|
|
|
"../Camlp4.ml"; "../Camlp4Parsers.ml"; "../Camlp4Printers.ml";
|
|
|
|
"../Camlp4Filters.ml"; "../Camlp4Top.ml"]
|
|
|
|
|
|
|
|
let doc () =
|
|
|
|
pack (); just_doc ()
|