]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamlbuild/tools.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / ocamlbuild / tools.ml
1 (***********************************************************************)
2 (*                             ocamlbuild                              *)
3 (*                                                                     *)
4 (*  Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
5 (*                                                                     *)
6 (*  Copyright 2007 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
13 (* Original author: Nicolas Pouillard *)
14 (* Tools *)
15
16 open My_std
17 open Format
18 open Log
19 open Pathname.Operators
20 open Tags.Operators
21 open Rule
22
23 let pp_l = List.print String.print
24
25 let tags_of_pathname p =
26   Configuration.tags_of_filename (Pathname.to_string p)
27   ++("file:"^p)
28   ++("extension:"^Pathname.get_extension p)  
29 let flags_of_pathname p = Configuration.flags_of_filename (Pathname.to_string p)
30
31 let opt_print elt ppf =
32   function
33   | Some x -> fprintf ppf "@[<2>Some@ %a@]" elt x
34   | None -> pp_print_string ppf "None"
35
36 let path_and_context_of_string s =
37   if Pathname.is_implicit s then
38     let b = Pathname.basename s in
39     let d = Pathname.dirname s in
40     if d <> Pathname.current_dir_name then
41       let () = Pathname.define_context d [d] in
42       [s]
43     else
44       let include_dirs = Pathname.include_dirs_of d in
45       List.map (fun include_dir -> include_dir/b) include_dirs
46   else [s]
47