(***********************************************************************) (* *) (* OCaml *) (* *) (* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *) (* *) (* Copyright 2002 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. *) (* *) (***********************************************************************) open Format type error = | CannotRun of string | WrongMagic of string exception Error of error (* Optionally preprocess a source file *) let call_external_preprocessor sourcefile pp = let tmpfile = Filename.temp_file "ocamlpp" "" in let comm = Printf.sprintf "%s %s > %s" pp (Filename.quote sourcefile) tmpfile in if Ccomp.command comm <> 0 then begin Misc.remove_file tmpfile; raise (Error (CannotRun comm)); end; tmpfile let preprocess sourcefile = match !Clflags.preprocessor with None -> sourcefile | Some pp -> call_external_preprocessor sourcefile pp let remove_preprocessed inputfile = match !Clflags.preprocessor with None -> () | Some _ -> Misc.remove_file inputfile (* Note: some of the functions here should go to Ast_mapper instead, which would encapsulate the "binary AST" protocol. *) let write_ast magic ast = let fn = Filename.temp_file "camlppx" "" in let oc = open_out_bin fn in output_string oc magic; output_value oc !Location.input_name; output_value oc ast; close_out oc; fn let apply_rewriter magic fn_in ppx = let fn_out = Filename.temp_file "camlppx" "" in let comm = Printf.sprintf "%s %s %s" ppx (Filename.quote fn_in) (Filename.quote fn_out) in let ok = Ccomp.command comm = 0 in Misc.remove_file fn_in; if not ok then begin Misc.remove_file fn_out; raise (Error (CannotRun comm)); end; if not (Sys.file_exists fn_out) then raise (Error (WrongMagic comm)); (* check magic before passing to the next ppx *) let ic = open_in_bin fn_out in let buffer = try really_input_string ic (String.length magic) with End_of_file -> "" in close_in ic; if buffer <> magic then begin Misc.remove_file fn_out; raise (Error (WrongMagic comm)); end; fn_out let read_ast magic fn = let ic = open_in_bin fn in try let buffer = really_input_string ic (String.length magic) in assert(buffer = magic); (* already checked by apply_rewriter *) Location.input_name := input_value ic; let ast = input_value ic in close_in ic; Misc.remove_file fn; ast with exn -> close_in ic; Misc.remove_file fn; raise exn let rewrite magic ast ppxs = read_ast magic (List.fold_left (apply_rewriter magic) (write_ast magic ast) (List.rev ppxs)) let apply_rewriters_str ?(restore = true) ~tool_name ast = match !Clflags.all_ppx with | [] -> ast | ppxs -> let ast = Ast_mapper.add_ppx_context_str ~tool_name ast in let ast = rewrite Config.ast_impl_magic_number ast ppxs in Ast_mapper.drop_ppx_context_str ~restore ast let apply_rewriters_sig ?(restore = true) ~tool_name ast = match !Clflags.all_ppx with | [] -> ast | ppxs -> let ast = Ast_mapper.add_ppx_context_sig ~tool_name ast in let ast = rewrite Config.ast_intf_magic_number ast ppxs in Ast_mapper.drop_ppx_context_sig ~restore ast let apply_rewriters ?restore ~tool_name magic ast = if magic = Config.ast_impl_magic_number then Obj.magic (apply_rewriters_str ?restore ~tool_name (Obj.magic ast)) else if magic = Config.ast_intf_magic_number then Obj.magic (apply_rewriters_sig ?restore ~tool_name (Obj.magic ast)) else assert false (* Parse a file or get a dumped syntax tree from it *) exception Outdated_version let open_and_check_magic inputfile ast_magic = let ic = open_in_bin inputfile in let is_ast_file = try let buffer = really_input_string ic (String.length ast_magic) in if buffer = ast_magic then true else if String.sub buffer 0 9 = String.sub ast_magic 0 9 then raise Outdated_version else false with Outdated_version -> Misc.fatal_error "OCaml and preprocessor have incompatible versions" | _ -> false in (ic, is_ast_file) let file ppf ~tool_name inputfile parse_fun ast_magic = let (ic, is_ast_file) = open_and_check_magic inputfile ast_magic in let ast = try if is_ast_file then begin if !Clflags.fast then (* FIXME make this a proper warning *) fprintf ppf "@[Warning: %s@]@." "option -unsafe used with a preprocessor returning a syntax tree"; Location.input_name := input_value ic; input_value ic end else begin seek_in ic 0; Location.input_name := inputfile; let lexbuf = Lexing.from_channel ic in Location.init lexbuf inputfile; parse_fun lexbuf end with x -> close_in ic; raise x in close_in ic; apply_rewriters ~restore:false ~tool_name ast_magic ast let report_error ppf = function | CannotRun cmd -> fprintf ppf "Error while running external preprocessor@.\ Command line: %s@." cmd | WrongMagic cmd -> fprintf ppf "External preprocessor does not produce a valid file@.\ Command line: %s@." cmd let () = Location.register_error_of_exn (function | Error err -> Some (Location.error_of_printer_file report_error err) | _ -> None ) let parse_all ~tool_name parse_fun magic ppf sourcefile = Location.input_name := sourcefile; let inputfile = preprocess sourcefile in let ast = try file ppf ~tool_name inputfile parse_fun magic with exn -> remove_preprocessed inputfile; raise exn in remove_preprocessed inputfile; ast let parse_implementation ppf ~tool_name sourcefile = parse_all ~tool_name Parse.implementation Config.ast_impl_magic_number ppf sourcefile let parse_interface ppf ~tool_name sourcefile = parse_all ~tool_name Parse.interface Config.ast_intf_magic_number ppf sourcefile