Skip to content

Commit

Permalink
Expose the promote mode (#437)
Browse files Browse the repository at this point in the history
  • Loading branch information
jeremiedimino authored Jan 25, 2018
1 parent 39afb77 commit 437211f
Show file tree
Hide file tree
Showing 8 changed files with 202 additions and 52 deletions.
12 changes: 12 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,18 @@
- Use /Fo instead of -o when invoking the Microsoft C compiler to eliminate
deprecation warning when compiling C++ sources (#354)

- Add a mode field to `rule` stanzas:
+ `(mode standard)` is the default
+ `(mode fallback)` replaces `(fallback)`
+ `(mode promote)` means that targets are copied to the source tree
after the rule has completed
+ `(mode promote-until-clean)` is the same as `(mode promote)` except
that `jbuilder clean` deletes the files copied to the source tree.
(#437)

- Add a flag `--ignore-promoted-rules` to make jbuilder ignore rules
with `(mode promote)`. `-p` implies `--ignore-promoted-rules` (#437)

- Display a warning for invalid lines in jbuild-ignore (#389)

1.0+beta16 (05/11/2017)
Expand Down
66 changes: 43 additions & 23 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,23 +10,24 @@ let (>>=) = Future.(>>=)
let (>>|) = Future.(>>|)

type common =
{ concurrency : int
; debug_dep_path : bool
; debug_findlib : bool
; debug_backtraces : bool
; dev_mode : bool
; verbose : bool
; workspace_file : string option
; root : string
; target_prefix : string
; only_packages : String_set.t option
; capture_outputs : bool
; x : string option
; diff_command : string option
; auto_promote : bool
; force : bool
{ concurrency : int
; debug_dep_path : bool
; debug_findlib : bool
; debug_backtraces : bool
; dev_mode : bool
; verbose : bool
; workspace_file : string option
; root : string
; target_prefix : string
; only_packages : String_set.t option
; capture_outputs : bool
; x : string option
; diff_command : string option
; auto_promote : bool
; force : bool
; ignore_promoted_rules : bool
; (* Original arguments for the external-lib-deps hint *)
orig_args : string list
orig_args : string list
}

let prefix_target common s = common.target_prefix ^ s
Expand Down Expand Up @@ -82,6 +83,7 @@ module Main = struct
?only_packages:common.only_packages
?filter_out_optional_stanzas_with_missing_deps
?x:common.x
~ignore_promoted_rules:common.ignore_promoted_rules
()
end

Expand Down Expand Up @@ -176,7 +178,10 @@ let common =
diff_command
auto_promote
force
(root, only_packages, orig)
(root,
only_packages,
ignore_promoted_rules,
orig)
x
=
let root, to_cwd =
Expand Down Expand Up @@ -205,6 +210,7 @@ let common =
; diff_command
; auto_promote
; force
; ignore_promoted_rules
; only_packages =
Option.map only_packages
~f:(fun s -> String_set.of_list (String.split s ~on:','))
Expand Down Expand Up @@ -309,6 +315,12 @@ let common =
~doc:"Force actions associated to aliases to be re-executed even
if their dependencies haven't changed.")
in
let ignore_promoted_rules =
Arg.(value
& flag
& info ["ignore-promoted-rules"] ~docs
~doc:"Ignore rules with (mode promote)")
in
let for_release = "for-release-of-packages" in
let frop =
Arg.(value
Expand All @@ -320,32 +332,40 @@ let common =
packages as well as getting reproducible builds.|})
in
let root_and_only_packages =
let merge root only_packages release =
let merge root only_packages ignore_promoted_rules release =
let fail opt =
`Error (true,
sprintf
"Cannot use -p/--%s and %s simultaneously"
for_release opt)
in
match release, root, only_packages with
| Some _, Some _, _ -> fail "--root"
| Some _, _, Some _ -> fail "--only-packages"
| Some pkgs, None, None ->
match release, root, only_packages, ignore_promoted_rules with
| Some _, Some _, _, _ -> fail "--root"
| Some _, _, Some _, _ -> fail "--only-packages"
| Some _, _, _, true -> fail "--ignore-promoted-rules"
| Some pkgs, None, None, false ->
`Ok (Some ".",
Some pkgs,
true,
["-p"; pkgs]
)
| None, _, _ ->
| None, _, _, _ ->
`Ok (root,
only_packages,
ignore_promoted_rules,
List.concat
[ dump_opt "--root" root
; dump_opt "--only-packages" only_packages
; if ignore_promoted_rules then
["--ignore-promoted-rules"]
else
[]
])
in
Term.(ret (const merge
$ root
$ only_packages
$ ignore_promoted_rules
$ frop))
in
let x =
Expand Down
61 changes: 55 additions & 6 deletions doc/jbuild.rst
Original file line number Diff line number Diff line change
Expand Up @@ -294,12 +294,10 @@ See the `User actions`_ section for more details.
- ``(deps (<deps-conf list>))`` to specify the dependencies of the
rule. See the `Dependency specification`_ section for more details.

- ``(fallback)`` to specify that this is a fallback rule. A fallback
rule means that if the targets are already present in the source
tree, jbuilder will ignore the rule. It is an error if only a subset
of the targets are present in the tree. The common use of fallback
rules is to generate default configuration files that may be
generated by a configure script.
- ``(mode <mode>)`` to specify how to handle the targets, see `mode`_
for details

- ``(fallback)`` is deprecated and is the same as ``(mode fallback)``

- ``(locks (<lock-names>))`` specify that the action must be run while
holding the following locks. See the `Locks`_ section for more details.
Expand All @@ -308,6 +306,41 @@ Note that contrary to makefiles or other build systems, user rules currently
don't support patterns, such as a rule to produce ``%.y`` from ``%.x`` for any
given ``%``. This might be supported in the future.

modes
~~~~~

By default, the target of a rule must not exist in the source tree and
Jbuilder will error out when this is the case.

However, it is possible to change this behavior using the ``mode``
field. The following modes are available:

- ``standard``, this is the standard mode

- ``fallback``, in this mode, when the targets are already present in
the source tree, jbuilder will ignore the rule. It is an error if
only a subset of the targets are present in the tree. The common use
of fallback rules is to generate default configuration files that
may be generated by a configure script.

- ``promote``, in this mode, the files in the source tree will be
ignored. Once the rule has been executed, the targets will be copied
back to the source tree

- ``promote-until-clean`` is the same as ``promote`` except than
``jbuilder clean`` will remove the promoted files from the source
tree


There are two use cases for promote rules. The first one is when the
generated code is easier to review than the generator, so it's easier
to commit the generated code and review it. The second is to cut down
dependencies during releases: by passing ``--ignore-promoted-rules``
to jbuilder, rules will ``(mode promote)`` will be ignored and the
source files will be used instead. The
``-p/--for-release-of-packages`` flag implies
``--ignore-promote-rules``.

inferred rules
~~~~~~~~~~~~~~

Expand Down Expand Up @@ -359,6 +392,14 @@ ocamllex
(deps (<name>.mll))
(action (chdir ${ROOT} (run ${bin:ocamllex} -q -o ${<})))))
To use a different rule mode, use the long form:

.. code:: scheme
(ocamllex
((modules (<names>))
(mode <mode>)))
ocamlyacc
---------

Expand All @@ -371,6 +412,14 @@ ocamlyacc
(deps (<name>.mly))
(action (chdir ${ROOT} (run ${bin:ocamlyacc} ${<})))))
To use a different rule mode, use the long form:

.. code:: scheme
(ocamlyacc
((modules (<names>))
(mode <mode>)))
menhir
------

Expand Down
74 changes: 61 additions & 13 deletions src/jbuild.ml
Original file line number Diff line number Diff line change
Expand Up @@ -738,6 +738,16 @@ module Rule = struct
| Promote_but_delete_on_clean
| Not_a_rule_stanza
| Ignore_source_files

let t =
enum
[ "standard" , Standard
; "fallback" , Fallback
; "promote" , Promote
; "promote-unil-clean", Promote_but_delete_on_clean
]

let field = field "mode" t ~default:Standard
end

type t =
Expand Down Expand Up @@ -765,19 +775,51 @@ module Rule = struct
field "deps" (list Dep_conf.t) ~default:[] >>= fun deps ->
field "action" Action.Unexpanded.t >>= fun action ->
field "locks" (list String_with_vars.t) ~default:[] >>= fun locks ->
field_b "fallback" >>= fun fallback ->
map_validate
(field_b "fallback" >>= fun fallback ->
field_o "mode" Mode.t >>= fun mode ->
return (fallback, mode))
~f:(function
| true, Some _ ->
Error "Cannot use both (fallback) and (mode ...) at the same time.\n\
(fallback) is the same as (mode fallback), \
please use the latter in new code."
| false, Some mode -> Ok mode
| true, None -> Ok Fallback
| false, None -> Ok Standard)
>>= fun mode ->
return { targets = Static targets
; deps
; action
; mode = if fallback then Fallback else Standard
; mode
; locks
; loc = Loc.none
})
sexp

let ocamllex_v1 loc names =
type lex_or_yacc =
{ modules : string list
; mode : Mode.t
}

let ocamllex_v1 sexp =
match sexp with
| List (_, List (_, _) :: _) ->
record
(field "modules" (list string) >>= fun modules ->
Mode.field >>= fun mode ->
return { modules; mode })
sexp
| _ ->
{ modules = list string sexp
; mode = Standard
}

let ocamlyacc_v1 = ocamllex_v1

let ocamllex_to_rule loc { modules; mode } =
let module S = String_with_vars in
List.map names ~f:(fun name ->
List.map modules ~f:(fun name ->
let src = name ^ ".mll" in
let dst = name ^ ".ml" in
{ targets = Static [dst]
Expand All @@ -791,14 +833,14 @@ module Rule = struct
; S.virt_var __POS__ "@"
; S.virt_var __POS__"<"
]))
; mode = Not_a_rule_stanza
; mode
; locks = []
; loc
})

let ocamlyacc_v1 loc names =
let ocamlyacc_to_rule loc { modules; mode } =
let module S = String_with_vars in
List.map names ~f:(fun name ->
List.map modules ~f:(fun name ->
let src = name ^ ".mly" in
{ targets = Static [name ^ ".ml"; name ^ ".mli"]
; deps = [File (S.virt_text __POS__ src)]
Expand All @@ -807,7 +849,7 @@ module Rule = struct
(S.virt_var __POS__ "ROOT",
Run (S.virt_text __POS__ "ocamlyacc",
[S.virt_var __POS__ "<"]))
; mode = Not_a_rule_stanza
; mode
; locks = []
; loc
})
Expand All @@ -818,17 +860,20 @@ module Menhir = struct
{ merge_into : string option
; flags : String_with_vars.t list
; modules : string list
; mode : Rule.Mode.t
}

let v1 =
record
(field_o "merge_into" string >>= fun merge_into ->
field "flags" (list String_with_vars.t) ~default:[] >>= fun flags ->
field "modules" (list string) >>= fun modules ->
Rule.Mode.field >>= fun mode ->
return
{ merge_into
; flags
; modules
; mode
}
)

Expand All @@ -847,7 +892,7 @@ module Menhir = struct
(S.virt_var __POS__ "ROOT",
Run (S.virt_text __POS__ "menhir",
t.flags @ [S.virt_var __POS__ "<"]))
; mode = Not_a_rule_stanza
; mode = t.mode
; locks = []
; loc
})
Expand All @@ -867,7 +912,7 @@ module Menhir = struct
; t.flags
; [ S.virt_var __POS__ "^" ]
]))
; mode = Not_a_rule_stanza
; mode = t.mode
; locks = []
; loc
}]
Expand Down Expand Up @@ -962,9 +1007,12 @@ module Stanzas = struct
; cstr "executable" (Executables.v1_single pkgs @> nil) execs
; cstr "executables" (Executables.v1_multi pkgs @> nil) execs
; cstr_loc "rule" (Rule.v1 @> nil) (fun loc x -> [Rule { x with loc }])
; cstr_loc "ocamllex" (list string @> nil) (fun loc x -> rules (Rule.ocamllex_v1 loc x))
; cstr_loc "ocamlyacc" (list string @> nil) (fun loc x -> rules (Rule.ocamlyacc_v1 loc x))
; cstr_loc "menhir" (Menhir.v1 @> nil) (fun loc x -> rules (Menhir.v1_to_rule loc x))
; cstr_loc "ocamllex" (Rule.ocamllex_v1 @> nil)
(fun loc x -> rules (Rule.ocamllex_to_rule loc x))
; cstr_loc "ocamlyacc" (Rule.ocamlyacc_v1 @> nil)
(fun loc x -> rules (Rule.ocamlyacc_to_rule loc x))
; cstr_loc "menhir" (Menhir.v1 @> nil)
(fun loc x -> rules (Menhir.v1_to_rule loc x))
; cstr "install" (Install_conf.v1 pkgs @> nil) (fun x -> [Install x])
; cstr "alias" (Alias_conf.v1 pkgs @> nil) (fun x -> [Alias x])
; cstr "copy_files" (Copy_files.v1 @> nil)
Expand Down
Loading

0 comments on commit 437211f

Please sign in to comment.