Merge commit 'ocaml3102'
[ocaml.git] / ocamlbuild / signatures.mli
blob34ecc6515e6f628066c2edf2ec0a4706e893cfed
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 (***********************************************************************)
12 (* $Id$ *)
13 (* Original author: Nicolas Pouillard *)
14 (** This module contains all module signatures that the user
15 could use to build an ocamlbuild plugin. *)
17 module type OrderedTypePrintable = sig
18 type t
19 val compare : t -> t -> int
20 val print : Format.formatter -> t -> unit
21 end
23 module type SET = sig
24 include Set.S
25 val find : (elt -> bool) -> t -> elt
26 val map : (elt -> elt) -> t -> t
27 val of_list : elt list -> t
28 val print : Format.formatter -> t -> unit
29 end
31 module type LIST = sig
32 (* Added functions *)
33 val print : (Format.formatter -> 'a -> 'b) -> Format.formatter -> 'a list -> unit
34 val filter_opt : ('a -> 'b option) -> 'a list -> 'b list
35 val union : 'a list -> 'a list -> 'a list
37 (* Original functions *)
38 include Std_signatures.LIST
39 end
41 module type STRING = sig
42 val print : Format.formatter -> string -> unit
43 val chomp : string -> string
45 (** [before s n] returns the substring of all characters of [s]
46 that precede position [n] (excluding the character at
47 position [n]).
48 This is the same function as {!Str.string_before}. *)
49 val before : string -> int -> string
51 (** [after s n] returns the substring of all characters of [s]
52 that follow position [n] (including the character at
53 position [n]).
54 This is the same function as {!Str.string_after}. *)
55 val after : string -> int -> string
57 val first_chars : string -> int -> string
58 (** [first_chars s n] returns the first [n] characters of [s].
59 This is the same function as {!before} ant {!Str.first_chars}. *)
61 val last_chars : string -> int -> string
62 (** [last_chars s n] returns the last [n] characters of [s].
63 This is the same function as {!Str.last_chars}. *)
65 val eq_sub_strings : string -> int -> string -> int -> int -> bool
67 (** [is_prefix u v] is u a prefix of v ? *)
68 val is_prefix : string -> string -> bool
69 (** [is_suffix u v] : is v a suffix of u ? *)
70 val is_suffix : string -> string -> bool
72 (** [contains_string s1 p2 s2] Search in [s1] starting from [p1] if it
73 contains the [s2] string. Returns [Some position] where [position]
74 is the begining of the string [s2] in [s1], [None] otherwise. *)
75 val contains_string : string -> int -> string -> int option
77 (** [subst patt repl text] *)
78 val subst : string -> string -> string -> string
80 (** [tr patt repl text] *)
81 val tr : char -> char -> string -> string
83 val rev : string -> string
85 (* Convert a character list into a character string *)
86 val implode : char list -> string
88 (* Convert a character string into a character list *)
89 val explode : string -> char list
91 (** The following are original functions from the [String] module. *)
92 include Std_signatures.STRING
93 end
95 module type TAGS = sig
96 include Set.S with type elt = string
97 val of_list : string list -> t
98 val print : Format.formatter -> t -> unit
99 val does_match : t -> t -> bool
100 module Operators : sig
101 val ( ++ ) : t -> elt -> t
102 val ( -- ) : t -> elt -> t
103 val ( +++ ) : t -> elt option -> t
104 val ( --- ) : t -> elt option -> t
108 module type PATHNAME = sig
109 type t = string
110 val concat : t -> t -> t
111 val compare : t -> t -> int
112 val equal : t -> t -> bool
113 val exists : t -> bool
114 val mk : string -> t
115 val define_context : string -> string list -> unit
116 val include_dirs_of : string -> string list
117 val copy : t -> t -> unit
118 val to_string : t -> string
119 val print : Format.formatter -> t -> unit
120 val current_dir_name : t
121 val parent_dir_name : t
122 val read : t -> string
123 val same_contents : t -> t -> bool
124 val basename : t -> t
125 val dirname : t -> t
126 val is_relative : t -> bool
127 val readlink : t -> t
128 val readdir : t -> t array
129 val is_link : t -> bool
130 val is_directory : t -> bool
132 val add_extension : string -> t -> t
133 val check_extension : t -> string -> bool
135 val get_extension : t -> string
136 val remove_extension : t -> t
137 val update_extension : string -> t -> t
139 val get_extensions : t -> string
140 val remove_extensions : t -> t
141 val update_extensions : string -> t -> t
143 val print_path_list : Format.formatter -> t list -> unit
144 val pwd : t
145 val parent : t -> t
146 (** [is_prefix x y] is [x] a pathname prefix of [y] *)
147 val is_prefix : t -> t -> bool
148 val is_implicit : t -> bool
149 module Operators : sig
150 val ( / ) : t -> t -> t
151 val ( -.- ) : t -> string -> t
155 (** Provides an abstract type for easily building complex shell commands without making
156 quotation mistakes. *)
157 module type COMMAND = sig
158 type tags
159 type pathname
161 (** The type [t] provides some basic combinators and command primitives.
162 Other commands can be made of command specifications ([spec]). *)
163 type t =
164 | Seq of t list (** A sequence of commands (like the `;' in shell) *)
165 | Cmd of spec (** A command is made of command specifications ([spec]) *)
166 | Echo of string list * pathname (** Write the given strings (w/ any formatting) to the given file *)
167 | Nop (** The command that does nothing *)
169 (** The type for command specifications. *)
170 and spec =
171 | N (** No operation. *)
172 | S of spec list (** A sequence. This gets flattened in the last stages *)
173 | A of string (** An atom. *)
174 | P of pathname (** A pathname. *)
175 | Px of pathname (** A pathname, that will also be given to the call_with_target hook. *)
176 | Sh of string (** A bit of raw shell code, that will not be escaped. *)
177 | T of tags (** A set of tags, that describe properties and some semantics
178 information about the command, afterward these tags will be
179 replaced by command [spec]s (flags for instance). *)
180 | V of string (** A virtual command, that will be resolved at execution using [resolve_virtuals] *)
181 | Quote of spec (** A string that should be quoted like a filename but isn't really one. *)
183 (*type v = [ `Seq of v list | `Cmd of vspec | `Nop ]
184 and vspec =
185 [ `N
186 | `S of vspec list
187 | `A of string
188 | `P of pathname
189 | `Px of pathname
190 | `Sh of string
191 | `Quote of vspec ]
193 val spec_of_vspec : vspec -> spec
194 val vspec_of_spec : spec -> vspec
195 val t_of_v : v -> t
196 val v_of_t : t -> v*)
198 (** Will convert a string list to a list of atoms by adding [A] constructors. *)
199 val atomize : string list -> spec
201 (** Will convert a string list to a list of paths by adding [P] constructors. *)
202 val atomize_paths : string list -> spec
204 (** Run the command. *)
205 val execute : ?quiet:bool -> ?pretend:bool -> t -> unit
207 (** Run the commands in the given list, if possible in parallel.
208 See the module [Ocamlbuild_executor]. *)
209 val execute_many : ?quiet:bool -> ?pretend:bool -> t list -> (bool list * exn) option
211 (** [setup_virtual_command_solver virtual_command solver]
212 the given solver can raise Not_found if it fails to find a valid
213 command for this virtual command. *)
214 val setup_virtual_command_solver : string -> (unit -> spec) -> unit
216 (** Search the given command in the command path and return its absolute
217 pathname. *)
218 val search_in_path : string -> string
220 (** Simplify a command by flattening the sequences and resolving the tags
221 into command-line options. *)
222 val reduce : spec -> spec
224 (** Print a command (the format is not suitable to running the command). *)
225 val print : Format.formatter -> t -> unit
227 (** Convert a command to a string (same format as print). *)
228 val to_string : t -> string
230 (** Build a string representation of a command that can be passed to the
231 system calls. *)
232 val string_of_command_spec : spec -> string
235 (** A self-contained module implementing extended shell glob patterns who have an expressive power
236 equal to boolean combinations of regular expressions. *)
237 module type GLOB = sig
239 (** A globber is a boolean combination of basic expressions indented to work on
240 pathnames. Known operators
241 are [or], [and] and [not], which may also be written [|], [&] and [~]. There are
242 also constants [true] and [false] (or [1] and [0]). Expression can be grouped
243 using parentheses.
244 - [true] matches anything,
245 - [false] matches nothing,
246 - {i basic} [or] {i basic} matches strings matching either one of the basic expressions,
247 - {i basic} [and] {i basic} matches strings matching both basic expressions,
248 - not {i basic} matches string that don't match the basic expression,
249 - {i basic} matches strings that match the basic expression.
251 A basic expression can be a constant string enclosed in double quotes, in which
252 double quotes must be preceded by backslashes, or a glob pattern enclosed between a [<] and a [>],
253 - ["]{i string}["] matches the literal string {i string},
254 - [<]{i glob}[>] matches the glob pattern {i glob}.
256 A glob pattern is an anchored regular expression in a shell-like syntax. Most characters stand for themselves.
257 Character ranges are given in usual shell syntax between brackets. The star [*] stands for any sequence of
258 characters. The joker '?' stands for exactly one, unspecified character. Alternation is achieved using braces [{].
259 - {i glob1}{i glob2} matches strings who have a prefix matching {i glob1} and the corresponding suffix
260 matching {i glob2}.
261 - [a] matches the string consisting of the single letter [a].
262 - [{]{i glob1},{i glob2}[}] matches strings matching {i glob1} or {i glob2}.
263 - [?] any one-letter string, excluding the slash.
264 - [*] matches all strings not containing a slash, including the empty one.
265 - [**/] the empty string, or any string ending with a slash.
266 - [/**] any string starting with a slash, or the empty string.
267 - [/**/] any string starting and ending with a slash.
268 - [\[]{i c1}-{i c2}{i c3}-{i c4}...[\]] matches characters in the range {i c1} to {i c2} inclusive,
269 or in the range {i c3} to {i c4} inclusive. For instance [\[a-fA-F0-9\]] matches hexadecimal digits.
270 To match the dash, put it at the end.
273 (** The type representing globbers. Do not attempt to compare them, as they get on-the-fly optimizations. *)
274 type globber
276 (** [parse ~dir pattern] will parse the globber pattern [pattern], optionally prefixing its patterns with [dir]. *)
277 val parse : ?dir:string -> string -> globber
279 (** A descriptive exception raised when an invalid glob pattern description is given. *)
280 exception Parse_error of string
282 (** [eval g u] returns [true] if and only if the string [u] matches the given glob expression. Avoid reparsing
283 the same pattern, since the automaton implementing the pattern is optimized on the fly. The first few evaluations
284 are done using a time-inefficient but memory-efficient algorithm. It then compiles the pattern into an efficient
285 but more memory-hungry data structure. *)
286 val eval : globber -> string -> bool
289 (** Module for modulating the logging output with the logging level. *)
290 module type LOG = sig
291 (** Current logging (debugging) level. *)
292 val level : int ref
294 (** [dprintf level fmt args...] formats the logging information [fmt]
295 with the arguments [args...] on the logging output if the logging
296 level is greater than or equal to [level]. The default level is 1.
297 More obscure debugging information should have a higher logging
298 level. Youre formats are wrapped inside these two formats
299 ["@\[<2>"] and ["@\]@."]. *)
300 val dprintf : int -> ('a, Format.formatter, unit) format -> 'a
302 (** Equivalent to calling [dprintf] with a level [< 0]. *)
303 val eprintf : ('a, Format.formatter, unit) format -> 'a
305 (** Same as dprintf but without the format wrapping. *)
306 val raw_dprintf : int -> ('a, Format.formatter, unit) format -> 'a
309 module type OUTCOME = sig
310 type ('a,'b) t =
311 | Good of 'a
312 | Bad of 'b
314 val wrap : ('a -> 'b) -> 'a -> ('b, exn) t
315 val ignore_good : ('a, exn) t -> unit
316 val good : ('a, exn) t -> 'a
319 module type MISC = sig
320 val opt_print :
321 (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a option -> unit
322 val the : 'a option -> 'a
323 val getenv : ?default:string -> string -> string
324 val with_input_file : ?bin:bool -> string -> (in_channel -> 'a) -> 'a
325 val with_output_file : ?bin:bool -> string -> (out_channel -> 'a) -> 'a
326 val with_temp_file : string -> string -> (string -> 'a) -> 'a
327 val read_file : string -> string
328 val copy_chan : in_channel -> out_channel -> unit
329 val copy_file : string -> string -> unit
330 val print_string_list : Format.formatter -> string list -> unit
332 (** A shortcut to force lazy value (See {Lazy.force}). *)
333 val ( !* ) : 'a Lazy.t -> 'a
335 (** The right associative application.
336 Useful when writing to much parentheses:
337 << f (g x ... t) >> becomes << f& g x ... t >>
338 << f (g (h x)) >> becomes << f& g& h x >> *)
339 val ( & ) : ('a -> 'b) -> 'a -> 'b
341 (** The reversed application combinator.
342 Useful to describe some operations chaining.
343 << f x (g y (h z)) >> becomes << z |> h |> g y |> f x >> *)
344 val ( |> ) : 'a -> ('a -> 'b) -> 'b
346 (** [r @:= l] is equivalent to [r := !r @ l] *)
347 val ( @:= ) : 'a list ref -> 'a list -> unit
349 val memo : ('a -> 'b) -> ('a -> 'b)
352 module type OPTIONS = sig
353 type command_spec
355 val build_dir : string ref
356 val include_dirs : string list ref
357 val exclude_dirs : string list ref
358 val nothing_should_be_rebuilt : bool ref
359 val ocamlc : command_spec ref
360 val ocamlopt : command_spec ref
361 val ocamldep : command_spec ref
362 val ocamldoc : command_spec ref
363 val ocamlyacc : command_spec ref
364 val ocamllex : command_spec ref
365 val ocamlrun : command_spec ref
366 val ocamlmklib : command_spec ref
367 val ocamlmktop : command_spec ref
368 val hygiene : bool ref
369 val sanitize : bool ref
370 val sanitization_script : string ref
371 val ignore_auto : bool ref
372 val plugin : bool ref
373 val just_plugin : bool ref
374 val native_plugin : bool ref
375 val make_links : bool ref
376 val nostdlib : bool ref
377 val program_to_execute : bool ref
378 val must_clean : bool ref
379 val catch_errors : bool ref
380 val use_menhir : bool ref
381 val show_documentation : bool ref
382 val recursive : bool ref
384 val targets : string list ref
385 val ocaml_libs : string list ref
386 val ocaml_cflags : string list ref
387 val ocaml_lflags : string list ref
388 val ocaml_ppflags : string list ref
389 val ocaml_yaccflags : string list ref
390 val ocaml_lexflags : string list ref
391 val program_args : string list ref
392 val ignore_list : string list ref
393 val tags : string list ref
394 val tag_lines : string list ref
395 val show_tags : string list ref
397 val ext_obj : string ref
398 val ext_lib : string ref
399 val ext_dll : string ref
402 module type ARCH = sig
403 type 'a arch = private
404 | Arch_dir of string * 'a * 'a arch list
405 | Arch_dir_pack of string * 'a * 'a arch list
406 | Arch_file of string * 'a
408 val dir : string -> unit arch list -> unit arch
409 val dir_pack : string -> unit arch list -> unit arch
410 val file : string -> unit arch
412 type info = private {
413 current_path : string;
414 include_dirs : string list;
415 for_pack : string;
418 val annotate : 'a arch -> info arch
420 val print : (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a arch -> unit
421 val print_include_dirs : Format.formatter -> string list -> unit
422 val print_info : Format.formatter -> info -> unit
424 val iter_info : ('a -> unit) -> 'a arch -> unit
425 val fold_info : ('a -> 'b -> 'b) -> 'a arch -> 'b -> 'b
427 val iter_include_dirs : info arch -> (string -> unit) -> unit
429 val mk_tables :
430 info arch -> (string, string list) Hashtbl.t * (string, string) Hashtbl.t
431 val print_table :
432 (Format.formatter -> 'a -> unit) -> Format.formatter -> (string, 'a) Hashtbl.t -> unit
435 (** This module contains the functions and values that can be used by plugins. *)
436 module type PLUGIN = sig
437 module Pathname : PATHNAME
438 module Tags : TAGS
439 module Command : COMMAND with type tags = Tags.t and type pathname = Pathname.t
440 module Outcome : OUTCOME
441 module String : STRING
442 module List : LIST
443 module StringSet : Set.S with type elt = String.t
444 module Options : OPTIONS with type command_spec = Command.spec
445 module Arch : ARCH
446 include MISC
448 (** See [COMMAND] for the description of these types. *)
449 type command = Command.t = Seq of command list | Cmd of spec | Echo of string list * Pathname.t | Nop
450 and spec = Command.spec =
451 | N | S of spec list | A of string | P of string | Px of string
452 | Sh of string | T of Tags.t | V of string | Quote of spec
454 (** [path1/path2] Join the given path names. *)
455 val ( / ) : Pathname.t -> Pathname.t -> Pathname.t
457 (** [path-.-extension] Add the given extension to the given pathname. *)
458 val ( -.- ) : Pathname.t -> string -> Pathname.t
460 (** [tags++tag] Add the given tag to the given set of tags. *)
461 val ( ++ ) : Tags.t -> Tags.elt -> Tags.t
463 (** [tags--tag] Remove the given tag to the given set of tags. *)
464 val ( -- ) : Tags.t -> Tags.elt -> Tags.t
466 (** [tags+++optional_tag] Add the given optional tag to the given set of tags
467 if the given option is Some. *)
468 val ( +++ ) : Tags.t -> Tags.elt option -> Tags.t
470 (** [tags---optional_tag] Remove the given optional tag to the given set of tags
471 if the given option is Some. *)
472 val ( --- ) : Tags.t -> Tags.elt option -> Tags.t
474 (** The type of the builder environments. Here an environment is just the
475 lookup function of it. Basically this function will resolve path variables
476 like % or more generally %(var_name). *)
477 type env = Pathname.t -> Pathname.t
479 (** A builder is a function that waits for conjonction of alternative targets.
480 The alternatives are here to support some choices, for instance for an
481 OCaml module an alternatives can be foo.cmo, foo.cmi, Foo.cmo, Foo.cmi.
482 Conjonctions are here to help making parallelism, indeed commands that are
483 independant will be run concurently. *)
484 type builder = Pathname.t list list -> (Pathname.t, exn) Outcome.t list
486 (** This is the type for rule actions. An action receive as argument, the
487 environment lookup function (see [env]), and a function to dynamically
488 build more targets (see [builder]). An action should return the command
489 to run in order to build the rule productions using the rule dependencies. *)
490 type action = env -> builder -> Command.t
492 (** This is the main function for adding a rule to the ocamlbuild engine.
493 - The first argument is the name of the rule (should be unique).
494 - It takes files that the rule produces.
495 Use ~prod for one file, ~prods for list of files.
496 - It also takes files that the rule uses.
497 Use ~dep for one file, ~deps for list of files.
498 - It finally takes the action to perform in order to produce the
499 productions files using the dependencies (see [action]).
500 There is also two more options:
501 - The ~insert argument allow to insert the rules precisely between other
502 rules.
503 - The ~stamp argument specify the name of a file that will be
504 automatically produced by ocamlbuild. This file can serve as a virtual
505 target (or phony target), since it will be filled up by a digest of
506 it dependencies.
507 - The ~tags argument in deprecated, don't use it. *)
508 val rule : string ->
509 ?tags:string list ->
510 ?prods:string list ->
511 ?deps:string list ->
512 ?prod:string ->
513 ?dep:string ->
514 ?stamp:string ->
515 ?insert:[`top | `before of string | `after of string | `bottom] ->
516 action -> unit
518 (** [copy_rule name ?insert source destination] *)
519 val copy_rule : string ->
520 ?insert:[`top | `before of string | `after of string | `bottom] ->
521 string -> string -> unit
523 (** [dep tags deps] Will build [deps] when all [tags] will be activated. *)
524 val dep : Tags.elt list -> Pathname.t list -> unit
526 (** [flag tags command_spec] Will inject the given piece of command
527 ([command_spec]) when all [tags] will be activated. *)
528 val flag : Tags.elt list -> Command.spec -> unit
530 (** [non_dependency module_path module_name]
531 Example:
532 [non_dependency "foo/bar/baz" "Goo"]
533 Says that the module [Baz] in the file [foo/bar/baz.*] does not depend on [Goo]. *)
534 val non_dependency : Pathname.t -> string -> unit
536 (** [use_lib module_path lib_path]*)
537 val use_lib : Pathname.t -> Pathname.t -> unit
539 (** [ocaml_lib <options> library_pathname]
540 Declare an ocaml library.
542 Example: ocaml_lib "foo/bar"
543 This will setup the tag use_bar tag.
544 At link time it will include:
545 foo/bar.cma or foo/bar.cmxa
546 If you supply the ~dir:"boo" option -I boo
547 will be added at link and compile time.
548 Use ~extern:true for non-ocamlbuild handled libraries.
549 Use ~byte:false or ~native:false to disable byte or native mode.
550 Use ~tag_name:"usebar" to override the default tag name. *)
551 val ocaml_lib :
552 ?extern:bool ->
553 ?byte:bool ->
554 ?native:bool ->
555 ?dir:Pathname.t ->
556 ?tag_name:string ->
557 Pathname.t -> unit
559 (** [expand_module include_dirs module_name extensions]
560 Example:
561 [expand_module ["a";"b";"c"] "Foo" ["cmo";"cmi"] =
562 ["a/foo.cmo"; "a/Foo.cmo"; "a/foo.cmi"; "a/Foo.cmi";
563 "b/foo.cmo"; "b/Foo.cmo"; "b/foo.cmi"; "b/Foo.cmi";
564 "c/foo.cmo"; "c/Foo.cmo"; "c/foo.cmi"; "c/Foo.cmi"]] *)
565 val expand_module :
566 Pathname.t list -> Pathname.t -> string list -> Pathname.t list
568 (** Reads the given file, parse it has list of words separated by blanks.
569 It ignore lines that begins with a '#' character. *)
570 val string_list_of_file : Pathname.t -> string list
572 (** Takes a pathname and returns an OCaml module name. Basically it will
573 remove directories and extensions, and then capitalize the string. *)
574 val module_name_of_pathname : Pathname.t -> string
576 (** The Unix mv command. *)
577 val mv : Pathname.t -> Pathname.t -> Command.t
579 (** The Unix cp command. *)
580 val cp : Pathname.t -> Pathname.t -> Command.t
582 (** The Unix ln -f command. *)
583 val ln_f : Pathname.t -> Pathname.t -> Command.t
585 (** The Unix ln -s command. *)
586 val ln_s : Pathname.t -> Pathname.t -> Command.t
588 (** The Unix rm -f command. *)
589 val rm_f : Pathname.t -> Command.t
591 (** The Unix chmod command (almost deprecated). *)
592 val chmod : Command.spec -> Pathname.t -> Command.t
594 (** The Unix cmp command (almost deprecated). *)
595 val cmp : Pathname.t -> Pathname.t -> Command.t
597 (** [hide_package_contents pack_name]
598 Don't treat the given package as an open package.
599 So a module will not be replaced during linking by
600 this package even if it contains that module. *)
601 val hide_package_contents : string -> unit
603 (** [tag_file filename tag_list] Tag the given filename with all given tags. *)
604 val tag_file : Pathname.t -> Tags.elt list -> unit
606 (** [tag_any tag_list] Tag anything with all given tags. *)
607 val tag_any : Tags.elt list -> unit
609 (** Returns the set of tags that applies to the given pathname. *)
610 val tags_of_pathname : Pathname.t -> Tags.t
612 (** Here is the list of hooks that the dispatch function have to handle.
613 Generally one respond to one or two hooks (like After_rules) and do
614 nothing in the default case. *)
615 type hook =
616 | Before_hygiene
617 | After_hygiene
618 | Before_options
619 | After_options
620 | Before_rules
621 | After_rules
623 (** [dispatch hook_handler] Is the entry point for ocamlbuild plugins. Every
624 plugin must call it with a [hook_handler] where all calls to plugin
625 functions lives. *)
626 val dispatch : (hook -> unit) -> unit