]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamlbuild/rule.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / ocamlbuild / rule.mli
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 open My_std
15 open Resource
16
17 type env = Pathname.t -> Pathname.t
18 type builder = Pathname.t list list -> (Pathname.t, exn) Outcome.t list
19 type action = env -> builder -> Command.t
20
21 type 'a gen_rule
22
23 type rule = Pathname.t gen_rule
24 type rule_scheme = resource_pattern gen_rule
25
26 type 'a rule_printer = (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a gen_rule -> unit
27
28 (** This exception can be raised inside the action of a rule to make the
29     algorithm skip this rule. *)
30 exception Failed
31
32 val name_of_rule : 'a gen_rule -> string
33 val deps_of_rule : 'a gen_rule -> Pathname.t list
34 val prods_of_rule : 'a gen_rule -> 'a list
35
36 val rule : string ->
37   ?tags:string list ->
38   ?prods:string list ->
39   ?deps:string list ->
40   ?prod:string ->
41   ?dep:string ->
42   ?stamp:string ->
43   ?insert:[`top | `before of string | `after of string | `bottom] ->
44   action -> unit
45
46 (** [copy_rule name ?insert source destination] *)
47 val copy_rule : string ->
48   ?insert:[`top | `before of string | `after of string | `bottom] ->
49   string -> string -> unit
50
51 module Common_commands : sig
52   val mv : Pathname.t -> Pathname.t -> Command.t
53   val cp : Pathname.t -> Pathname.t -> Command.t
54   val cp_p : Pathname.t -> Pathname.t -> Command.t
55   val ln_f : Pathname.t -> Pathname.t -> Command.t
56   val ln_s : Pathname.t -> Pathname.t -> Command.t
57   val rm_f : Pathname.t -> Command.t
58   val chmod : Command.spec -> Pathname.t -> Command.t
59   val cmp : Pathname.t -> Pathname.t -> Command.t
60 end
61
62 val print : Format.formatter -> rule -> unit
63 val pretty_print : 'a rule_printer
64
65 (** For system use only *)
66
67 val subst : Resource.env -> rule_scheme -> rule
68 val can_produce : Pathname.t -> rule_scheme -> rule option
69 (* val tags_matches : Tags.t -> t -> t option *)
70 val compare : 'a gen_rule -> 'a gen_rule -> int
71
72 val print_rule_name : Format.formatter -> 'a gen_rule -> unit
73 val print_rule_contents : 'a rule_printer
74
75 val get_rules : unit -> rule_scheme list
76 val clear_rules : unit -> unit
77
78 val call : builder -> rule -> unit
79
80 val build_deps_of_tags : builder -> Tags.t -> Pathname.t list