]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/ocamldoc/odoc.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / ocamldoc / odoc.ml
1 (***********************************************************************)
2 (*                             OCamldoc                                *)
3 (*                                                                     *)
4 (*            Maxence Guesdon, projet Cristal, INRIA Rocquencourt      *)
5 (*                                                                     *)
6 (*  Copyright 2001 Institut National de Recherche en Informatique et   *)
7 (*  en Automatique.  All rights reserved.  This file is distributed    *)
8 (*  under the terms of the Q Public License version 1.0.               *)
9 (*                                                                     *)
10 (***********************************************************************)
11
12 (* $Id: odoc.ml 9371 2009-10-16 12:40:04Z doligez $ *)
13
14 (** Main module for bytecode. *)
15
16 open Config
17 open Clflags
18 open Misc
19 open Format
20 open Typedtree
21
22 module M = Odoc_messages
23
24 let print_DEBUG s = print_string s ; print_newline ()
25
26 (* we check if we must load a module given on the command line *)
27 let arg_list = Array.to_list Sys.argv
28 let (cm_opt, paths) =
29   let rec iter (f_opt, inc) = function
30       [] | _ :: [] -> (f_opt, inc)
31     | "-g" :: file :: q when
32         ((Filename.check_suffix file "cmo") or
33          (Filename.check_suffix file "cma") or
34            (Filename.check_suffix file "cmxs")) &
35         (f_opt = None) ->
36       iter (Some file, inc) q
37   | "-i" :: dir :: q ->
38       iter (f_opt, inc @ [dir]) q
39   | _ :: q ->
40         iter (f_opt, inc) q
41   in
42   iter (None, []) arg_list
43
44 let _ = print_DEBUG "Fin analyse des arguments pour le dynamic load"
45
46 (** Return the real name of the file to load,
47    searching it in the paths if it is
48    a simple name and not in the current directory. *)
49 let get_real_filename name =
50    if Filename.basename name <> name then
51      name
52    else
53      (
54       let paths = Filename.current_dir_name :: paths @ [Odoc_config.custom_generators_path] in
55       try
56         let d = List.find
57             (fun d -> Sys.file_exists (Filename.concat d name))
58             paths
59         in
60         Filename.concat d name
61       with
62         Not_found ->
63           failwith (M.file_not_found_in_paths paths name)
64      )
65
66 let _ =
67   match cm_opt with
68     None ->
69       ()
70   | Some file ->
71       let file = Dynlink.adapt_filename file in
72       Dynlink.allow_unsafe_modules true;
73       try
74         let real_file = get_real_filename file in
75         ignore(Dynlink.loadfile real_file)
76       with
77         Dynlink.Error e ->
78           prerr_endline (Odoc_messages.load_file_error file (Dynlink.error_message e)) ;
79           exit 1
80       | Not_found ->
81           prerr_endline (Odoc_messages.load_file_error file "Not_found");
82           exit 1
83       | Sys_error s
84       | Failure s ->
85           prerr_endline (Odoc_messages.load_file_error file s);
86           exit 1
87
88 let _ = print_DEBUG "Fin du chargement dynamique eventuel"
89
90 let default_html_generator = new Odoc_html.html
91 let default_latex_generator = new Odoc_latex.latex
92 let default_texi_generator = new Odoc_texi.texi
93 let default_man_generator = new Odoc_man.man
94 let default_dot_generator = new Odoc_dot.dot
95 let _ = Odoc_args.parse
96     (default_html_generator :> Odoc_args.doc_generator)
97     (default_latex_generator :> Odoc_args.doc_generator)
98     (default_texi_generator :> Odoc_args.doc_generator)
99     (default_man_generator :> Odoc_args.doc_generator)
100     (default_dot_generator :> Odoc_args.doc_generator)
101
102
103 let loaded_modules =
104   List.flatten
105     (List.map
106        (fun f ->
107          Odoc_info.verbose (Odoc_messages.loading f);
108          try
109            let l = Odoc_analyse.load_modules f in
110            Odoc_info.verbose Odoc_messages.ok;
111            l
112          with Failure s ->
113            prerr_endline s ;
114            incr Odoc_global.errors ;
115            []
116        )
117        !Odoc_args.load
118     )
119
120 let modules = Odoc_analyse.analyse_files ~init: loaded_modules !Odoc_args.files
121
122 let _ =
123   match !Odoc_args.dump with
124     None -> ()
125   | Some f ->
126       try Odoc_analyse.dump_modules f modules
127       with Failure s ->
128         prerr_endline s ;
129         incr Odoc_global.errors
130
131 let _ =
132   match !Odoc_args.doc_generator with
133     None ->
134       ()
135   | Some gen ->
136       Odoc_info.verbose Odoc_messages.generating_doc;
137       gen#generate modules;
138       Odoc_info.verbose Odoc_messages.ok
139
140 let _ =
141   if !Odoc_global.errors > 0 then
142   (
143    prerr_endline (Odoc_messages.errors_occured !Odoc_global.errors) ;
144    exit 1
145   )
146   else
147     exit 0
148
149
150 (* eof $Id: odoc.ml 9371 2009-10-16 12:40:04Z doligez $ *)