Skip to content

Commit

Permalink
Add ${build-number}
Browse files Browse the repository at this point in the history
Fix #255
  • Loading branch information
jeremiedimino committed Mar 11, 2018
1 parent 5286b42 commit ced9c7c
Show file tree
Hide file tree
Showing 8 changed files with 52 additions and 1 deletion.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,8 @@ next
- Make sure modules in the current directory always have precedence
over included directories (#597)

- Add a `${build-number}` variable counting the number of builds. This
can be used to force running an action on every run of jbuilder

1.0+beta18 (25/02/2018)
-----------------------
Expand Down
4 changes: 4 additions & 0 deletions doc/jbuild.rst
Original file line number Diff line number Diff line change
Expand Up @@ -747,6 +747,10 @@ In addition, ``(action ...)`` fields support the following special variables:
file
- ``read-strings:<path>`` expands to the list of lines in the given
file, unescaped using OCaml lexical convention
- ``build-number`` expands to the number of times a build has been
started. This counter is reset when ``jbuilder clean`` is called. Using
this variable in an action will effectively cause it to be
executed everytime jbuilder runs

The ``${<kind>:...}`` forms are what allows you to write custom rules that work
transparently whether things are installed or not.
Expand Down
17 changes: 16 additions & 1 deletion src/build_system.ml
Original file line number Diff line number Diff line change
Expand Up @@ -339,7 +339,8 @@ type t =
; file_tree : File_tree.t
; mutable local_mkdirs : Path.Local.Set.t
; mutable dirs : (Path.t, Dir_status.t) Hashtbl.t
; mutable gen_rules : (dir:Path.t -> string list -> extra_sub_directories_to_keep) String_map.t
; mutable gen_rules :
(dir:Path.t -> string list -> extra_sub_directories_to_keep) String_map.t
; mutable load_dir_stack : Path.t list
; (* Set of directories under _build that have at least one rule and
all their ancestors. *)
Expand Down Expand Up @@ -1173,8 +1174,22 @@ let eval_request t ~request ~process_target =
let dyn_deps = Build_exec.exec_nop t request () in
process_targets (Pset.diff dyn_deps static_deps))

let build_number_file = Path.relative Path.build_dir ".build-number"

let increment_build_number t =
let fname = Path.to_string build_number_file in
let build_number =
if Sys.file_exists fname then
Sexp.Of_sexp.int (Sexp.load ~mode:Single ~fname) + 1
else
0
in
make_local_dirs t (Pset.singleton Path.build_dir);
Io.write_file fname (Sexp.to_string (Sexp.To_sexp.int build_number))

let do_build t ~request =
entry_point t ~f:(fun () ->
increment_build_number t;
eval_request t ~request ~process_target:(wait_for_file t))

module Ir_set = Set.Make(Internal_rule)
Expand Down
4 changes: 4 additions & 0 deletions src/build_system.mli
Original file line number Diff line number Diff line change
Expand Up @@ -159,6 +159,10 @@ val do_build

(** {2 Other queries} *)

(** File that contains the number of times {!do_build} was
called. This counter is resett by [jbuilder clean]. *)
val build_number_file : Path.t

val is_target : t -> Path.t -> bool

(** Return all the library dependencies (as written by the user)
Expand Down
3 changes: 3 additions & 0 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -537,6 +537,9 @@ module Action = struct
| Alias -> Loc.fail loc "You cannot use ${@} in aliases."
| Static l -> Some (Paths (l, Split))
end
| "build-number" ->
add_ddep acc ~key
(Build.contents Build_system.build_number_file >>^ str_exp)
| _ ->
match String.lsplit2 var ~on:':' with
| Some ("path-no-dep", s) ->
Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/jbuild
Original file line number Diff line number Diff line change
Expand Up @@ -408,3 +408,13 @@
(progn
(run ${exe:cram.exe} run.t)
(diff? run.t run.t.corrected)))))))

(alias
((name runtest)
(deps ((files_recursively_in test-cases/build-number)))
(action
(chdir test-cases/build-number
(setenv JBUILDER ${bin:jbuilder}
(progn
(run ${exe:cram.exe} run.t)
(diff? run.t run.t.corrected)))))))
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/build-number/jbuild
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(alias
((name x)
(action (echo "Build number: ${build-number}"))))
10 changes: 10 additions & 0 deletions test/blackbox-tests/test-cases/build-number/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
$ $JBUILDER build --root . -j 1 --display quiet @x
Build number: 0
$ $JBUILDER build --root . -j 1 --display quiet @x
Build number: 1
$ $JBUILDER build --root . -j 1 --display quiet @x
Build number: 2
$ $JBUILDER build --root . -j 1 --display quiet @x
Build number: 3
$ $JBUILDER build --root . -j 1 --display quiet @x
Build number: 4

0 comments on commit ced9c7c

Please sign in to comment.