2002-03-27 08:20:32 -08:00
|
|
|
(***********************************************************************)
|
|
|
|
(* OCamldoc *)
|
|
|
|
(* *)
|
|
|
|
(* Maxence Guesdon, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2001 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. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
2003-11-24 02:44:07 -08:00
|
|
|
(* $Id$ *)
|
2002-03-27 08:20:32 -08:00
|
|
|
|
|
|
|
(** Main module for bytecode. *)
|
|
|
|
|
|
|
|
open Config
|
|
|
|
open Clflags
|
|
|
|
open Misc
|
|
|
|
open Format
|
|
|
|
open Typedtree
|
|
|
|
|
2004-01-28 05:36:20 -08:00
|
|
|
module M = Odoc_messages
|
|
|
|
|
2006-09-20 04:14:37 -07:00
|
|
|
let print_DEBUG s = print_string s ; print_newline ()
|
2002-03-27 08:20:32 -08:00
|
|
|
|
|
|
|
(* we check if we must load a module given on the command line *)
|
|
|
|
let arg_list = Array.to_list Sys.argv
|
2009-03-11 00:04:39 -07:00
|
|
|
let (cm_opt, paths) =
|
2002-03-27 08:20:32 -08:00
|
|
|
let rec iter (f_opt, inc) = function
|
|
|
|
[] | _ :: [] -> (f_opt, inc)
|
|
|
|
| "-g" :: file :: q when
|
2002-07-23 07:12:03 -07:00
|
|
|
((Filename.check_suffix file "cmo") or
|
2009-03-11 00:04:39 -07:00
|
|
|
(Filename.check_suffix file "cma") or
|
|
|
|
(Filename.check_suffix file "cmxs")) &
|
2002-07-23 07:12:03 -07:00
|
|
|
(f_opt = None) ->
|
2009-03-11 00:04:39 -07:00
|
|
|
iter (Some file, inc) q
|
|
|
|
| "-i" :: dir :: q ->
|
|
|
|
iter (f_opt, inc @ [dir]) q
|
|
|
|
| _ :: q ->
|
2002-07-23 07:12:03 -07:00
|
|
|
iter (f_opt, inc) q
|
2002-03-27 08:20:32 -08:00
|
|
|
in
|
2004-07-13 05:25:21 -07:00
|
|
|
iter (None, []) arg_list
|
2002-03-27 08:20:32 -08:00
|
|
|
|
|
|
|
let _ = print_DEBUG "Fin analyse des arguments pour le dynamic load"
|
|
|
|
|
2006-09-20 04:14:37 -07:00
|
|
|
(** Return the real name of the file to load,
|
2004-01-28 05:36:20 -08:00
|
|
|
searching it in the paths if it is
|
|
|
|
a simple name and not in the current directory. *)
|
|
|
|
let get_real_filename name =
|
|
|
|
if Filename.basename name <> name then
|
|
|
|
name
|
|
|
|
else
|
|
|
|
(
|
2004-07-13 05:25:21 -07:00
|
|
|
let paths = Filename.current_dir_name :: paths @ [Odoc_config.custom_generators_path] in
|
2004-01-28 05:36:20 -08:00
|
|
|
try
|
2010-01-22 04:48:24 -08:00
|
|
|
let d = List.find
|
|
|
|
(fun d -> Sys.file_exists (Filename.concat d name))
|
|
|
|
paths
|
|
|
|
in
|
|
|
|
Filename.concat d name
|
2004-01-28 05:36:20 -08:00
|
|
|
with
|
2010-01-22 04:48:24 -08:00
|
|
|
Not_found ->
|
|
|
|
failwith (M.file_not_found_in_paths paths name)
|
2004-01-28 05:36:20 -08:00
|
|
|
)
|
|
|
|
|
2002-03-27 08:20:32 -08:00
|
|
|
let _ =
|
2009-03-11 00:04:39 -07:00
|
|
|
match cm_opt with
|
2002-03-27 08:20:32 -08:00
|
|
|
None ->
|
|
|
|
()
|
|
|
|
| Some file ->
|
2009-03-11 00:04:39 -07:00
|
|
|
let file = Dynlink.adapt_filename file in
|
2002-03-27 08:20:32 -08:00
|
|
|
Dynlink.allow_unsafe_modules true;
|
|
|
|
try
|
2004-01-28 05:36:20 -08:00
|
|
|
let real_file = get_real_filename file in
|
|
|
|
ignore(Dynlink.loadfile real_file)
|
2002-03-27 08:20:32 -08:00
|
|
|
with
|
2006-09-20 04:14:37 -07:00
|
|
|
Dynlink.Error e ->
|
2002-07-23 07:12:03 -07:00
|
|
|
prerr_endline (Odoc_messages.load_file_error file (Dynlink.error_message e)) ;
|
|
|
|
exit 1
|
|
|
|
| Not_found ->
|
|
|
|
prerr_endline (Odoc_messages.load_file_error file "Not_found");
|
2006-09-20 04:14:37 -07:00
|
|
|
exit 1
|
2004-01-28 05:36:20 -08:00
|
|
|
| Sys_error s
|
2010-01-20 08:26:46 -08:00
|
|
|
| Failure s ->
|
2002-07-23 07:12:03 -07:00
|
|
|
prerr_endline (Odoc_messages.load_file_error file s);
|
2006-09-20 04:14:37 -07:00
|
|
|
exit 1
|
2002-03-27 08:20:32 -08:00
|
|
|
|
2010-01-20 08:26:46 -08:00
|
|
|
let _ = print_DEBUG "Fin du chargement dynamique eventuel"
|
2002-03-27 08:20:32 -08:00
|
|
|
|
|
|
|
let default_html_generator = new Odoc_html.html
|
|
|
|
let default_latex_generator = new Odoc_latex.latex
|
2002-04-05 03:25:22 -08:00
|
|
|
let default_texi_generator = new Odoc_texi.texi
|
2002-03-27 08:20:32 -08:00
|
|
|
let default_man_generator = new Odoc_man.man
|
|
|
|
let default_dot_generator = new Odoc_dot.dot
|
|
|
|
let _ = Odoc_args.parse
|
|
|
|
(default_html_generator :> Odoc_args.doc_generator)
|
|
|
|
(default_latex_generator :> Odoc_args.doc_generator)
|
2002-04-05 03:25:22 -08:00
|
|
|
(default_texi_generator :> Odoc_args.doc_generator)
|
2002-03-27 08:20:32 -08:00
|
|
|
(default_man_generator :> Odoc_args.doc_generator)
|
|
|
|
(default_dot_generator :> Odoc_args.doc_generator)
|
|
|
|
|
|
|
|
|
|
|
|
let loaded_modules =
|
2006-09-20 04:14:37 -07:00
|
|
|
List.flatten
|
|
|
|
(List.map
|
2002-03-27 08:20:32 -08:00
|
|
|
(fun f ->
|
2002-07-23 07:12:03 -07:00
|
|
|
Odoc_info.verbose (Odoc_messages.loading f);
|
2006-09-20 04:14:37 -07:00
|
|
|
try
|
2002-07-23 07:12:03 -07:00
|
|
|
let l = Odoc_analyse.load_modules f in
|
|
|
|
Odoc_info.verbose Odoc_messages.ok;
|
|
|
|
l
|
2006-09-20 04:14:37 -07:00
|
|
|
with Failure s ->
|
|
|
|
prerr_endline s ;
|
2002-07-23 07:12:03 -07:00
|
|
|
incr Odoc_global.errors ;
|
|
|
|
[]
|
2002-03-27 08:20:32 -08:00
|
|
|
)
|
|
|
|
!Odoc_args.load
|
|
|
|
)
|
|
|
|
|
|
|
|
let modules = Odoc_analyse.analyse_files ~init: loaded_modules !Odoc_args.files
|
|
|
|
|
|
|
|
let _ =
|
|
|
|
match !Odoc_args.dump with
|
|
|
|
None -> ()
|
|
|
|
| Some f ->
|
|
|
|
try Odoc_analyse.dump_modules f modules
|
2006-09-20 04:14:37 -07:00
|
|
|
with Failure s ->
|
2002-07-23 07:12:03 -07:00
|
|
|
prerr_endline s ;
|
|
|
|
incr Odoc_global.errors
|
2002-03-27 08:20:32 -08:00
|
|
|
|
2006-09-20 04:14:37 -07:00
|
|
|
let _ =
|
2002-03-27 08:20:32 -08:00
|
|
|
match !Odoc_args.doc_generator with
|
|
|
|
None ->
|
|
|
|
()
|
2006-09-20 04:14:37 -07:00
|
|
|
| Some gen ->
|
2002-03-27 08:20:32 -08:00
|
|
|
Odoc_info.verbose Odoc_messages.generating_doc;
|
|
|
|
gen#generate modules;
|
|
|
|
Odoc_info.verbose Odoc_messages.ok
|
|
|
|
|
2006-09-20 04:14:37 -07:00
|
|
|
let _ =
|
2002-03-27 08:20:32 -08:00
|
|
|
if !Odoc_global.errors > 0 then
|
|
|
|
(
|
|
|
|
prerr_endline (Odoc_messages.errors_occured !Odoc_global.errors) ;
|
|
|
|
exit 1
|
|
|
|
)
|
|
|
|
else
|
|
|
|
exit 0
|