2007-02-07 00:59:16 -08:00
|
|
|
(***********************************************************************)
|
2012-08-01 07:47:00 -07:00
|
|
|
(* *)
|
2007-02-07 00:59:16 -08:00
|
|
|
(* ocamlbuild *)
|
|
|
|
(* *)
|
|
|
|
(* Nicolas Pouillard, Berke Durak, projet Gallium, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
|
|
|
(* Copyright 2007 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. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
2009-03-03 08:54:58 -08:00
|
|
|
|
2007-02-07 00:59:16 -08:00
|
|
|
(* Original author: Nicolas Pouillard *)
|
|
|
|
open My_std
|
|
|
|
open Resource
|
|
|
|
|
|
|
|
type env = Pathname.t -> Pathname.t
|
|
|
|
type builder = Pathname.t list list -> (Pathname.t, exn) Outcome.t list
|
|
|
|
type action = env -> builder -> Command.t
|
|
|
|
|
2007-11-21 13:06:10 -08:00
|
|
|
type 'a gen_rule
|
2007-02-07 00:59:16 -08:00
|
|
|
|
2007-11-21 08:40:28 -08:00
|
|
|
type rule = Pathname.t gen_rule
|
|
|
|
type rule_scheme = resource_pattern gen_rule
|
|
|
|
|
|
|
|
type 'a rule_printer = (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a gen_rule -> unit
|
|
|
|
|
2008-07-25 07:50:47 -07:00
|
|
|
(** This exception can be raised inside the action of a rule to make the
|
|
|
|
algorithm skip this rule. *)
|
|
|
|
exception Failed
|
|
|
|
|
2007-11-21 13:06:10 -08:00
|
|
|
val name_of_rule : 'a gen_rule -> string
|
|
|
|
val deps_of_rule : 'a gen_rule -> Pathname.t list
|
|
|
|
val prods_of_rule : 'a gen_rule -> 'a list
|
2013-09-15 04:36:02 -07:00
|
|
|
val doc_of_rule : 'a gen_rule -> string option
|
2007-11-21 13:06:10 -08:00
|
|
|
|
2007-02-07 00:59:16 -08:00
|
|
|
val rule : string ->
|
|
|
|
?tags:string list ->
|
|
|
|
?prods:string list ->
|
|
|
|
?deps:string list ->
|
|
|
|
?prod:string ->
|
|
|
|
?dep:string ->
|
2007-11-21 13:34:57 -08:00
|
|
|
?stamp:string ->
|
2007-02-07 00:59:16 -08:00
|
|
|
?insert:[`top | `before of string | `after of string | `bottom] ->
|
2013-09-15 04:36:02 -07:00
|
|
|
?doc:string ->
|
2007-02-07 00:59:16 -08:00
|
|
|
action -> unit
|
|
|
|
|
|
|
|
(** [copy_rule name ?insert source destination] *)
|
|
|
|
val copy_rule : string ->
|
|
|
|
?insert:[`top | `before of string | `after of string | `bottom] ->
|
|
|
|
string -> string -> unit
|
|
|
|
|
|
|
|
module Common_commands : sig
|
|
|
|
val mv : Pathname.t -> Pathname.t -> Command.t
|
|
|
|
val cp : Pathname.t -> Pathname.t -> Command.t
|
2007-10-08 07:19:34 -07:00
|
|
|
val cp_p : Pathname.t -> Pathname.t -> Command.t
|
2007-02-07 00:59:16 -08:00
|
|
|
val ln_f : Pathname.t -> Pathname.t -> Command.t
|
|
|
|
val ln_s : Pathname.t -> Pathname.t -> Command.t
|
|
|
|
val rm_f : Pathname.t -> Command.t
|
|
|
|
val chmod : Command.spec -> Pathname.t -> Command.t
|
|
|
|
val cmp : Pathname.t -> Pathname.t -> Command.t
|
|
|
|
end
|
|
|
|
|
2007-11-21 08:40:28 -08:00
|
|
|
val print : Format.formatter -> rule -> unit
|
|
|
|
val pretty_print : 'a rule_printer
|
2007-02-26 09:05:30 -08:00
|
|
|
|
2007-02-07 00:59:16 -08:00
|
|
|
(** For system use only *)
|
|
|
|
|
2007-11-21 08:40:28 -08:00
|
|
|
val subst : Resource.env -> rule_scheme -> rule
|
|
|
|
val can_produce : Pathname.t -> rule_scheme -> rule option
|
|
|
|
(* val tags_matches : Tags.t -> t -> t option *)
|
|
|
|
val compare : 'a gen_rule -> 'a gen_rule -> int
|
2007-02-07 00:59:16 -08:00
|
|
|
|
2007-11-21 08:40:28 -08:00
|
|
|
val print_rule_name : Format.formatter -> 'a gen_rule -> unit
|
|
|
|
val print_rule_contents : 'a rule_printer
|
2007-02-07 00:59:16 -08:00
|
|
|
|
2007-11-21 08:40:28 -08:00
|
|
|
val get_rules : unit -> rule_scheme list
|
2010-01-20 08:26:46 -08:00
|
|
|
val clear_rules : unit -> unit
|
2007-02-07 00:59:16 -08:00
|
|
|
|
2007-11-21 08:40:28 -08:00
|
|
|
val call : builder -> rule -> unit
|
2007-02-07 00:59:16 -08:00
|
|
|
|
|
|
|
val build_deps_of_tags : builder -> Tags.t -> Pathname.t list
|